eidolon/Handler/Upload.hs

337 lines
14 KiB
Haskell
Raw Normal View History

2015-01-18 19:44:41 +00:00
-- eidolon -- A simple gallery in Haskell and Yesod
-- Copyright (C) 2015 Amedeo Molnár
--
-- This program is free software: you can redistribute it and/or modify
-- it under the terms of the GNU Affero General Public License as published
-- by the Free Software Foundation, either version 3 of the License, or
-- (at your option) any later version.
--
-- This program is distributed in the hope that it will be useful,
-- but WITHOUT ANY WARRANTY; without even the implied warranty of
-- MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
-- GNU Affero General Public License for more details.
--
-- You should have received a copy of the GNU Affero General Public License
2015-01-21 09:00:18 +00:00
-- along with this program. If not, see <http://www.gnu.org/licenses/>.
2015-01-18 19:44:41 +00:00
module Handler.Upload where
2014-08-13 16:18:35 +00:00
import Import as I
import Handler.Commons
2014-08-13 16:18:35 +00:00
import Data.Time
import Data.Maybe
2014-09-24 21:03:18 +00:00
import qualified Data.Text as T
2015-01-16 00:23:02 +00:00
import Data.List as L
2014-12-02 07:02:40 +00:00
import qualified System.FilePath as FP
2016-05-04 00:27:24 +00:00
import System.Directory
2015-01-16 00:23:02 +00:00
import Text.Blaze.Internal
2016-05-04 00:27:24 +00:00
import Codec.ImageType
2016-11-19 21:13:02 +00:00
import Codec.Picture as P
2016-05-07 19:23:03 +00:00
import Codec.Picture.Metadata as PM
import Codec.Picture.ScaleDCT
2016-11-19 21:13:02 +00:00
import Graphics.Rasterific.Svg as SVG
import Graphics.Svg
import Graphics.Text.TrueType
2014-08-13 16:18:35 +00:00
2014-08-26 02:39:13 +00:00
getDirectUploadR :: AlbumId -> Handler Html
getDirectUploadR albumId = do
tempAlbum <- runDB $ get albumId
case tempAlbum of -- does the requested album exist
Just album -> do
2015-09-14 16:54:46 +00:00
let ownerId = albumOwner album
2014-08-26 02:39:13 +00:00
msu <- lookupSession "userId"
case msu of -- is anybody logged in
Just tempUserId -> do
2015-09-14 16:54:46 +00:00
let userId = getUserIdFromText tempUserId
if
userId == ownerId || userId `elem` albumShares album
-- is the owner present or a user with whom the album is shared
then do
2015-10-19 06:32:47 +00:00
(dUploadWidget, enctype) <- generateFormPost $ renderBootstrap3 BootstrapBasicForm $ dUploadForm userId albumId
2016-08-30 12:22:00 +00:00
defaultLayout $ do
2015-09-14 16:54:46 +00:00
setTitle $ toHtml ("Eidolon :: Upload medium to " `T.append` albumTitle album)
2014-08-26 02:39:13 +00:00
$(widgetFile "dUpload")
2015-09-14 16:54:46 +00:00
else do
2014-08-26 02:39:13 +00:00
setMessage "You must own this album to upload"
redirect $ AlbumR albumId
Nothing -> do
setMessage "You must be logged in to upload"
2015-09-14 16:54:46 +00:00
redirect LoginR
2014-08-26 02:39:13 +00:00
Nothing -> do
setMessage "This album does not exist"
2015-09-14 16:54:46 +00:00
redirect HomeR
2014-08-26 02:39:13 +00:00
postDirectUploadR :: AlbumId -> Handler Html
postDirectUploadR albumId = do
tempAlbum <- runDB $ get albumId
case tempAlbum of -- does the album exist
Just album -> do
2015-09-14 16:54:46 +00:00
let ownerId = albumOwner album
2014-08-26 02:39:13 +00:00
msu <- lookupSession "userId"
case msu of -- is anybody logged in
Just tempUserId -> do
2015-09-14 16:54:46 +00:00
let userId = getUserIdFromText tempUserId
2015-10-19 06:32:47 +00:00
if userId == ownerId || userId `elem` albumShares album
2015-09-14 16:54:46 +00:00
-- is the logged in user the owner or is the album shared with him
then do
2015-10-19 06:32:47 +00:00
((result, _), _) <- runFormPost $ renderBootstrap3 BootstrapBasicForm $ dUploadForm userId albumId
2014-08-26 02:39:13 +00:00
case result of
FormSuccess temp -> do
2015-09-14 16:54:46 +00:00
let fils = fileBulkFiles temp
let indFils = zip [1..] fils
2015-01-16 00:23:02 +00:00
errNames <- mapM
(\(index, file) -> do
2015-09-14 16:54:46 +00:00
let mime = fileContentType file
2016-05-04 00:27:24 +00:00
if mime `elem` acceptedTypes
2015-09-14 16:54:46 +00:00
then do
2015-01-16 00:23:02 +00:00
path <- writeOnDrive file ownerId albumId
2016-05-04 00:27:24 +00:00
isOk <- liftIO $ checkCVE_2016_3714 path mime
if isOk
then do
meta <- generateThumbs path ownerId albumId mime
2016-05-07 19:23:03 +00:00
tempName <- if length indFils == 1
2016-05-04 00:27:24 +00:00
then return $ fileBulkPrefix temp
else return (fileBulkPrefix temp `T.append` " " `T.append` T.pack (show (index :: Int)) `T.append` " of " `T.append` T.pack (show (length indFils)))
2016-09-06 15:30:41 +00:00
let medium = Medium tempName ('/' : path) ('/' : metaThumbPath meta) mime (fileBulkTime temp) (fileBulkOwner temp) (fileBulkDesc temp) (fileBulkTags temp) albumId ('/' : metaPreviewPath meta)
insertMedium medium albumId
2016-05-04 00:27:24 +00:00
return Nothing
else do
liftIO $ removeFile (FP.normalise path)
return $ Just $ fileName file
2015-09-14 16:54:46 +00:00
else
2015-01-16 00:23:02 +00:00
return $ Just $ fileName file
) indFils
2015-09-14 16:54:46 +00:00
let onlyErrNames = removeItem Nothing errNames
if
L.null onlyErrNames
then do
2015-01-16 00:23:02 +00:00
setMessage "All images succesfully uploaded"
2015-09-14 16:54:46 +00:00
redirect HomeR
else do
let justErrNames = map fromJust onlyErrNames
2016-11-19 21:13:02 +00:00
let msg = Content $ Text.Blaze.Internal.Text $ "File type not supported of: " `T.append` T.intercalate ", " justErrNames
2015-01-16 00:23:02 +00:00
setMessage msg
2015-09-14 16:54:46 +00:00
redirect HomeR
2014-08-26 02:39:13 +00:00
_ -> do
setMessage "There was an error uploading the file"
redirect $ DirectUploadR albumId
2015-09-14 16:54:46 +00:00
else do -- owner is not present
2014-08-26 02:39:13 +00:00
setMessage "You must own this album to upload"
redirect $ AlbumR albumId
Nothing -> do
setMessage "You must be logged in to upload"
redirect $ AlbumR albumId
Nothing -> do
setMessage "This Album does not exist"
redirect $ AlbumR albumId
2016-05-07 19:23:03 +00:00
-- | Type to pass metadata about imgaes around.
data ThumbsMeta = ThumbsMeta
{ metaThumbPath :: FP.FilePath -- ^ Filepath of the new thumbnail image
, metaPreviewPath :: FP.FilePath -- ^ Filepath of the new preview image
}
-- | generate thumbnail and preview images from uploaded image
generateThumbs
:: FP.FilePath -- ^ Path to original image
-> UserId -- ^ Uploading user
-> AlbumId -- ^ Destination album
-> T.Text -- ^ MIME-Type (used for svg et al.)
2016-05-07 19:23:03 +00:00
-> Handler ThumbsMeta -- ^ Resulting metadata to store
generateThumbs path uId aId mime = do
eimg <- liftIO $ readImage path
2016-11-19 21:13:02 +00:00
orig <- case eimg of
Left err -> -- This branch contains svg and other data formats. to be extended for pdf et al.
case mime of
"image/svg+xml" -> do
svg <- liftIO $ loadSvgFile path
(img, _) <- liftIO $ renderSvgDocument emptyFontCache Nothing 100 $ fromJust svg
return img
_ -> error err
Right img -> do -- This branch contains "classical" image formats like bmp or png
2016-11-19 21:13:02 +00:00
return $ convertRGBA8 img
let thumbName = FP.takeBaseName path ++ "_thumb.png"
prevName = FP.takeBaseName path ++ "_preview.png"
2016-11-19 21:13:02 +00:00
pathPrefix = "static" FP.</> "data" FP.</> T.unpack (extractKey uId) FP.</> T.unpack (extractKey aId)
tPath = pathPrefix FP.</> thumbName
pPath = pathPrefix FP.</> prevName
-- origPix = convertRGBA8 orig
oWidth = P.imageWidth orig :: Int
oHeight = P.imageHeight orig :: Int
tWidth = floor (fromIntegral oWidth / fromIntegral oHeight * fromIntegral tHeight :: Double)
tHeight = 230 :: Int
pHeight = 600 :: Int
pScale = (fromIntegral pHeight :: Double) / (fromIntegral oHeight :: Double)
pWidth = floor (fromIntegral oWidth * pScale)
tPix = scale (tWidth, tHeight) orig
pPix = scale (pWidth, pHeight) orig
liftIO $ savePngImage tPath $ ImageRGBA8 tPix
liftIO $ savePngImage pPath $ ImageRGBA8 pPix
2016-11-19 21:13:02 +00:00
return $ ThumbsMeta
{ metaThumbPath = tPath
, metaPreviewPath = pPath
}
2014-10-01 22:58:36 +00:00
2016-11-19 21:13:02 +00:00
checkCVE_2016_3714 :: FP.FilePath -> T.Text -> IO Bool
2016-05-04 00:27:24 +00:00
checkCVE_2016_3714 p m =
case m of
"image/jpeg" -> isJpeg p
"image/jpg" -> isJpeg p
"image/png" -> isPng p
"image/x-ms-bmp" -> isBmp p
"image/x-bmp" -> isBmp p
"image/bmp" -> isBmp p
"image/tiff" -> isTiff p
"image/tiff-fx" -> isTiff p
"image/svg+xml" -> return True -- TODO: have to check XML for that.
"image/gif" -> isGif p
_ -> return False
2014-12-02 07:02:40 +00:00
writeOnDrive :: FileInfo -> UserId -> AlbumId -> Handler FP.FilePath
writeOnDrive fil userId albumId = do
2014-12-03 22:30:13 +00:00
--filen <- return $ fileName fil
album <- runDB $ getJust albumId
let ac = albumContent album
[PersistInt64 int] = if L.null ac then [PersistInt64 1] else keyToValues $ maximum $ ac
filen = show $ fromIntegral int + 1
ext = FP.takeExtension $ T.unpack $ fileName fil
path = "static" FP.</> "data" FP.</> T.unpack (extractKey userId) FP.</> T.unpack (extractKey albumId) FP.</> filen ++ ext
2016-08-27 11:11:14 +00:00
dde <- liftIO $ doesDirectoryExist $ FP.dropFileName path
if not dde
then
liftIO $ createDirectoryIfMissing True $ FP.dropFileName path
else
return ()
2014-12-02 07:02:40 +00:00
liftIO $ fileMove fil path
2014-08-13 16:18:35 +00:00
return path
2015-10-19 06:32:47 +00:00
dUploadForm :: UserId -> AlbumId -> AForm Handler FileBulk
dUploadForm userId albumId = FileBulk
<$> areq textField (bfs ("Title" :: T.Text)) Nothing
2015-01-16 00:23:02 +00:00
<*> areq multiFileField "Select file(s)" Nothing
<*> lift (liftIO getCurrentTime)
<*> pure userId
2015-10-19 06:32:47 +00:00
<*> aopt textareaField (bfs ("Description" :: T.Text)) Nothing
<*> areq tagField (bfs ("Enter tags" :: T.Text)) Nothing
2015-01-16 00:23:02 +00:00
<*> pure albumId
2016-11-19 21:13:02 +00:00
<* bootstrapSubmit ("Upload" :: BootstrapSubmit T.Text)
2015-10-19 06:32:47 +00:00
2015-01-16 00:23:02 +00:00
data FileBulk = FileBulk
2016-11-19 21:13:02 +00:00
{ fileBulkPrefix :: T.Text
2015-01-16 00:23:02 +00:00
, fileBulkFiles :: [FileInfo]
, fileBulkTime :: UTCTime
, fileBulkOwner :: UserId
, fileBulkDesc :: Maybe Textarea
2016-11-19 21:13:02 +00:00
, fileBulkTags :: [T.Text]
2015-01-16 00:23:02 +00:00
, fileBulkAlbum :: AlbumId
}
getUploadR :: Handler Html
getUploadR = do
msu <- lookupSession "userId"
case msu of
Just tempUserId -> do
2015-09-14 16:54:46 +00:00
let userId = getUserIdFromText tempUserId
2015-01-16 00:23:02 +00:00
user <- runDB $ getJust userId
2015-09-14 16:54:46 +00:00
let albums = userAlbums user
if
I.null albums
then do
setMessage "Please create an album first"
redirect NewAlbumR
else do
2015-10-19 06:32:47 +00:00
(uploadWidget, enctype) <- generateFormPost $ renderBootstrap3 BootstrapBasicForm $ bulkUploadForm userId
2016-08-30 12:22:00 +00:00
defaultLayout $ do
2015-01-16 00:23:02 +00:00
setTitle "Eidolon :: Upload Medium"
$(widgetFile "bulkUpload")
Nothing -> do
setMessage "You need to be logged in"
2015-09-14 16:54:46 +00:00
redirect LoginR
2015-01-16 00:23:02 +00:00
2015-10-19 06:32:47 +00:00
bulkUploadForm :: UserId -> AForm Handler FileBulk
bulkUploadForm userId = (\a b c d e f g -> FileBulk b c d e f g a)
<$> areq (selectField albums) (bfs ("Album" :: T.Text)) Nothing
<*> areq textField (bfs ("Title" :: T.Text)) Nothing
2015-01-16 00:23:02 +00:00
<*> areq multiFileField "Select file(s)" Nothing
2014-08-13 16:18:35 +00:00
<*> lift (liftIO getCurrentTime)
2014-08-13 20:30:48 +00:00
<*> pure userId
2015-10-19 06:32:47 +00:00
<*> aopt textareaField (bfs ("Description" :: T.Text)) Nothing
<*> areq tagField (bfs ("Enter tags" :: T.Text)) Nothing
2016-11-19 21:13:02 +00:00
<* bootstrapSubmit ("Upload" :: BootstrapSubmit T.Text)
2014-08-13 22:52:32 +00:00
where
albums = do
allEnts <- runDB $ selectList [] [Desc AlbumTitle]
let entities = catMaybes $ map (\ent ->
2015-09-14 16:54:46 +00:00
if
userId == albumOwner (entityVal ent) || userId `elem` albumShares (entityVal ent)
then Just ent
else Nothing
) allEnts
2014-08-13 22:52:32 +00:00
optionsPairs $ I.map (\alb -> (albumTitle $ entityVal alb, entityKey alb)) entities
2014-08-13 16:18:35 +00:00
2015-01-16 00:23:02 +00:00
postUploadR :: Handler Html
postUploadR = do
msu <- lookupSession "userId"
case msu of
Just tempUserId -> do
2015-09-14 16:54:46 +00:00
let userId = getUserIdFromText tempUserId
2015-10-19 06:32:47 +00:00
((result, _), _) <- runFormPost $ renderBootstrap3 BootstrapBasicForm $ bulkUploadForm userId
2015-01-16 00:23:02 +00:00
case result of
FormSuccess temp -> do
2015-09-14 16:54:46 +00:00
let fils = fileBulkFiles temp
let indFils = zip [1..] fils
2015-01-16 00:23:02 +00:00
errNames <- mapM
(\(index, file) -> do
2015-09-14 16:54:46 +00:00
let mime = fileContentType file
2016-05-04 00:27:24 +00:00
if mime `elem` acceptedTypes
2015-09-14 16:54:46 +00:00
then do
let inAlbumId = fileBulkAlbum temp
2015-01-16 00:23:02 +00:00
albRef <- runDB $ getJust inAlbumId
2015-09-14 16:54:46 +00:00
let ownerId = albumOwner albRef
2015-01-16 00:23:02 +00:00
path <- writeOnDrive file ownerId inAlbumId
2016-05-04 00:27:24 +00:00
isOk <- liftIO $ checkCVE_2016_3714 path mime
if isOk
then do
meta <- generateThumbs path ownerId inAlbumId mime
2016-05-04 00:27:24 +00:00
tempName <- if
length indFils == 1
then return $ fileBulkPrefix temp
2016-05-07 19:23:03 +00:00
else
return
(fileBulkPrefix temp `T.append`
" " `T.append`
T.pack (show (index :: Int)) `T.append`
" of " `T.append`
T.pack (show (length indFils)))
2016-09-06 15:30:41 +00:00
let medium = Medium tempName ('/' : path) ('/' : metaThumbPath meta) mime (fileBulkTime temp) (fileBulkOwner temp) (fileBulkDesc temp) (fileBulkTags temp) inAlbumId ('/' : metaPreviewPath meta)
-- mId <- runDB $ I.insert medium
-- inALbum <- runDB $ getJust inAlbumId
-- let newMediaList = mId : albumContent inALbum
-- runDB $ update inAlbumId [AlbumContent =. newMediaList]
insertMedium medium inAlbumId
2016-05-04 00:27:24 +00:00
return Nothing
else do
liftIO $ removeFile (FP.normalise path)
return $ Just $ fileName file
2015-09-14 16:54:46 +00:00
else
2015-01-16 00:23:02 +00:00
return $ Just $ fileName file
) indFils
2015-09-14 16:54:46 +00:00
let onlyErrNames = removeItem Nothing errNames
if
L.null onlyErrNames
then do
2015-01-16 00:23:02 +00:00
setMessage "All images succesfully uploaded"
2015-09-14 16:54:46 +00:00
redirect HomeR
else do
let justErrNames = map fromJust onlyErrNames
2016-11-19 21:13:02 +00:00
let msg = Content $ Text.Blaze.Internal.Text $ "File type not supported of: " `T.append` T.intercalate ", " justErrNames
2015-01-16 00:23:02 +00:00
setMessage msg
2015-09-14 16:54:46 +00:00
redirect HomeR
2015-01-16 00:23:02 +00:00
_ -> do
setMessage "There was an error uploading the file"
2015-09-14 16:54:46 +00:00
redirect UploadR
2015-01-16 00:23:02 +00:00
Nothing -> do
setMessage "You need to be logged in"
2015-09-14 16:54:46 +00:00
redirect LoginR