eidolon/Handler/AdminMediumSettings.hs

148 lines
5.5 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
2014-09-09 02:25:47 +00:00
module Handler.AdminMediumSettings where
import Import
import Yesod.Text.Markdown
import Text.Markdown
2014-12-28 00:08:35 +00:00
import Handler.Commons
2014-09-09 02:25:47 +00:00
import System.FilePath
import qualified Data.Text as T
2014-09-09 02:25:47 +00:00
getAdminMediaR :: Handler Html
getAdminMediaR = do
2014-12-27 22:09:51 +00:00
adminCheck <- loginIsAdmin
case adminCheck of
Right _ -> do
media <- runDB $ selectList [] [Asc MediumTitle]
defaultLayout $ do
setTitle "Administration: Media"
$(widgetFile "adminMedia")
Left (errorMsg, route) -> do
setMessage errorMsg
2015-09-14 16:54:46 +00:00
redirect route
2014-09-09 02:25:47 +00:00
getAdminMediumSettingsR :: MediumId -> Handler Html
getAdminMediumSettingsR mediumId = do
2014-12-27 22:09:51 +00:00
adminCheck <- loginIsAdmin
case adminCheck of
Right _ -> do
tempMedium <- runDB $ get mediumId
case tempMedium of
Just medium -> do
2015-10-19 06:32:47 +00:00
(adminMediumSetWidget, enctype) <- generateFormPost $
renderBootstrap3 BootstrapBasicForm $
adminMediumSetForm medium
2016-09-07 15:32:56 +00:00
defaultLayout $ do
2014-12-27 22:09:51 +00:00
setTitle "Administration: Medium Settings"
$(widgetFile "adminMediumSet")
Nothing -> do
setMessage "This medium does not exist"
2015-09-14 16:54:46 +00:00
redirect AdminR
2014-12-27 22:09:51 +00:00
Left (errorMsg, route) -> do
setMessage errorMsg
2015-09-14 16:54:46 +00:00
redirect route
2014-09-09 02:25:47 +00:00
postAdminMediumSettingsR :: MediumId -> Handler Html
postAdminMediumSettingsR mediumId = do
2014-12-27 22:09:51 +00:00
adminCheck <- loginIsAdmin
case adminCheck of
Right _ -> do
tempMedium <- runDB $ get mediumId
case tempMedium of
Just medium -> do
2015-10-19 06:32:47 +00:00
((res, _), _) <- runFormPost $
renderBootstrap3 BootstrapBasicForm $
adminMediumSetForm medium
2014-12-27 22:09:51 +00:00
case res of
FormSuccess temp -> do
runDB $ update mediumId
[ MediumTitle =. mediumTitle temp
, MediumDescription =. mediumDescription temp
, MediumTags =. mediumTags temp
2016-12-19 01:27:09 +00:00
, MediumLicence =. mediumLicence temp
2014-12-27 22:09:51 +00:00
]
setMessage "Medium settings changed successfully"
2015-09-14 16:54:46 +00:00
redirect AdminR
2014-12-27 22:09:51 +00:00
_ -> do
setMessage "There was an error while changing the settings"
redirect $ AdminMediumSettingsR mediumId
Nothing -> do
setMessage "This medium does not exist"
2015-09-14 16:54:46 +00:00
redirect AdminR
2014-12-27 22:09:51 +00:00
Left (errorMsg, route) -> do
setMessage errorMsg
2015-09-14 16:54:46 +00:00
redirect route
2014-09-09 02:25:47 +00:00
2015-10-19 06:32:47 +00:00
adminMediumSetForm :: Medium -> AForm Handler Medium
adminMediumSetForm medium = Medium
<$> areq textField (bfs ("Title" :: T.Text)) (Just $ mediumTitle medium)
2014-09-09 02:25:47 +00:00
<*> pure (mediumPath medium)
2014-10-01 22:58:36 +00:00
<*> pure (mediumThumb medium)
2014-12-14 19:21:23 +00:00
<*> pure (mediumMime medium)
2014-09-09 02:25:47 +00:00
<*> pure (mediumTime medium)
<*> pure (mediumOwner medium)
<*> aopt markdownField (bfs ("Description" :: T.Text)) (Just $ mediumDescription medium)
2015-10-19 06:32:47 +00:00
<*> areq tagField (bfs ("Tags" :: T.Text)) (Just $ mediumTags medium)
2014-09-09 02:25:47 +00:00
<*> pure (mediumAlbum medium)
<*> pure (mediumPreview medium)
2016-12-18 23:28:07 +00:00
<*> areq (selectField licenses) (bfs ("Licence" :: T.Text)) (Just $ mediumLicence medium)
2015-10-19 06:32:47 +00:00
<* bootstrapSubmit ("Change settings" :: BootstrapSubmit Text)
2016-12-18 23:28:07 +00:00
where
2017-08-06 02:42:31 +00:00
licenses = optionsPairs $ map (\a -> (T.pack (show (a :: Licence)), a))
[minBound..maxBound]
2014-09-09 02:25:47 +00:00
getAdminMediumDeleteR :: MediumId -> Handler Html
getAdminMediumDeleteR mediumId = do
2014-12-27 22:09:51 +00:00
adminCheck <- loginIsAdmin
case adminCheck of
Right _ -> do
tempMedium <- runDB $ get mediumId
case tempMedium of
Just medium -> do
-- -- remove reference from album
-- let albumId = mediumAlbum medium
-- album <- runDB $ getJust albumId
-- let mediaList = albumContent album
-- let newMediaList = removeItem mediumId mediaList
-- runDB $ update albumId [AlbumContent =. newMediaList]
-- -- delete comments
-- commEnts <- runDB $ selectList [CommentOrigin ==. mediumId] []
-- _ <- mapM (\ent -> do
-- children <- runDB $ selectList [CommentParent ==. (Just $ entityKey ent)] []
-- _ <- mapM (\child -> do
-- -- delete comment children
-- runDB $ delete $ entityKey child
-- ) children
-- runDB $ delete $ entityKey ent) commEnts
-- -- delete medium
-- runDB $ delete mediumId
-- -- delete files
-- liftIO $ removeFile (normalise $ tail $ mediumPath medium)
-- liftIO $ removeFile (normalise $ tail $ mediumThumb medium)
-- liftIO $ removeFile (normalise $ tail $ mediumPreview medium)
2014-12-27 22:09:51 +00:00
-- outro
deleteMedium mediumId medium
2014-12-27 22:09:51 +00:00
setMessage "Medium deleted successfully"
2015-09-14 16:54:46 +00:00
redirect AdminR
2014-12-27 22:09:51 +00:00
Nothing -> do
setMessage "This medium does not exist"
2015-09-14 16:54:46 +00:00
redirect AdminR
2014-12-27 22:09:51 +00:00
Left (errorMsg, route) -> do
setMessage errorMsg
2015-09-14 16:54:46 +00:00
redirect route