eidolon/Handler/AdminProfileSettings.hs

190 lines
6.8 KiB
Haskell
Raw Permalink 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.AdminProfileSettings where
import Import
2014-12-28 00:08:35 +00:00
import Handler.Commons
import qualified Data.Text as T
import qualified Data.List as L
2014-12-27 22:09:51 +00:00
import Data.Maybe
import System.Directory
import System.FilePath
2014-09-07 04:56:34 +00:00
getAdminProfilesR :: Handler Html
getAdminProfilesR = do
2014-12-27 22:09:51 +00:00
adminCheck <- loginIsAdmin
case adminCheck of
Right _ -> do
2017-01-02 12:25:40 +00:00
profiles <- runDB $ selectList [] [Asc UserName]
2014-12-27 22:09:51 +00:00
defaultLayout $ do
setTitle "Administration: Profiles"
$(widgetFile "adminProfiles")
Left (errorMsg, route) -> do
setMessage errorMsg
2015-09-14 16:54:46 +00:00
redirect route
2014-09-08 01:57:17 +00:00
getAdminUserAlbumsR :: UserId -> Handler Html
getAdminUserAlbumsR ownerId = do
2014-12-27 22:09:51 +00:00
adminCheck <- loginIsAdmin
case adminCheck of
Right _ -> do
tempOwner <- runDB $ get ownerId
case tempOwner of
Just owner -> do
albums <- runDB $ selectList [AlbumOwner ==. ownerId] [Desc AlbumTitle]
defaultLayout $ do
setTitle "Administration: User albums"
$(widgetFile "adminUserAlbums")
Nothing -> do
setMessage "This user 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
getAdminUserMediaR :: UserId -> Handler Html
getAdminUserMediaR ownerId = do
2014-12-27 22:09:51 +00:00
adminCheck <- loginIsAdmin
case adminCheck of
Right _ -> do
tempOwner <- runDB $ get ownerId
case tempOwner of
Just owner -> do
media <- runDB $ selectList [MediumOwner ==. ownerId] [Desc MediumTitle]
defaultLayout $ do
setTitle "Administration: User media"
$(widgetFile "adminUserMedia")
Nothing -> do
setMessage "This user 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
getAdminProfileSettingsR :: UserId -> Handler Html
getAdminProfileSettingsR ownerId = do
2014-12-27 22:09:51 +00:00
adminCheck <- loginIsAdmin
case adminCheck of
Right _ -> do
tempOwner <- runDB $ get ownerId
case tempOwner of
Just owner -> do
2015-10-19 06:32:47 +00:00
(adminProfileSetWidget, enctype) <- generateFormPost $
renderBootstrap3 BootstrapBasicForm $
adminProfileForm owner
2016-09-07 15:32:56 +00:00
defaultLayout $ do
2014-12-27 22:09:51 +00:00
setTitle "Administration: Profile settings"
$(widgetFile "adminProfileSettings")
Nothing -> do
setMessage "This user 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
postAdminProfileSettingsR :: UserId -> Handler Html
postAdminProfileSettingsR ownerId = do
2014-12-27 22:09:51 +00:00
adminCheck <- loginIsAdmin
case adminCheck of
Right _ -> do
tempOwner <- runDB $ get ownerId
case tempOwner of
Just owner -> do
2015-10-19 06:32:47 +00:00
((result, _), _) <- runFormPost $
renderBootstrap3 BootstrapBasicForm $
adminProfileForm owner
2014-12-27 22:09:51 +00:00
case result of
FormSuccess temp -> do
runDB $ update ownerId
2015-09-14 16:54:46 +00:00
[ UserName =. userName temp
, UserSlug =. userSlug temp
, UserEmail =. userEmail temp
, UserAdmin =. userAdmin temp
2016-12-19 01:27:09 +00:00
, UserDefaultLicence =. userDefaultLicence temp
2014-12-27 22:09:51 +00:00
]
setMessage "User data updated 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"
redirect $ AdminProfileSettingsR ownerId
Nothing -> do
setMessage "This user 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
2015-10-19 06:32:47 +00:00
adminProfileForm :: User -> AForm Handler User
adminProfileForm owner = User
<$> areq textField (bfs ("Username" :: T.Text)) (Just $ userName owner)
<*> areq textField (bfs ("Userslug" :: T.Text)) (Just $ userSlug owner)
<*> areq emailField (bfs ("Email" :: T.Text)) (Just $ userEmail owner)
<*> pure (userSalt owner)
<*> pure (userSalted owner)
<*> pure (userAlbums owner)
2015-10-19 06:32:47 +00:00
<*> areq boolField (bfs ("Admin" :: T.Text)) (Just $ userAdmin owner)
2017-01-02 12:26:02 +00:00
<*> areq (selectField licenses) (bfs ("Default licence" :: T.Text)) (Just $ userDefaultLicence owner)
2017-04-24 05:46:34 +00:00
<*> pure (userActive owner)
2015-10-19 06:32:47 +00:00
<* bootstrapSubmit ("Change settings" :: BootstrapSubmit T.Text)
2017-01-02 12:26:02 +00:00
where
2017-08-06 02:42:31 +00:00
licenses = optionsPairs $ map (\a -> (T.pack (show (a :: Licence)), a))
[minBound..maxBound]
getAdminProfileDeleteR :: UserId -> Handler Html
getAdminProfileDeleteR ownerId = do
2014-12-27 22:09:51 +00:00
adminCheck <- loginIsAdmin
case adminCheck of
Right _ -> do
tempOwner <- runDB $ get ownerId
case tempOwner of
Just owner -> do
2015-09-14 16:54:46 +00:00
let albumList = userAlbums owner
2016-09-05 15:17:57 +00:00
mapM_ (\albumId -> do
2014-12-27 22:09:51 +00:00
album <- runDB $ getJust albumId
2015-09-14 16:54:46 +00:00
let mediaList = albumContent album
2016-09-05 15:17:57 +00:00
mapM_ (\med -> do
2014-12-27 22:09:51 +00:00
-- delete comments
commEnts <- runDB $ selectList [CommentOrigin ==. med] []
2016-09-05 15:17:57 +00:00
mapM_ (\ent -> do
children <- runDB $ selectList [CommentParent ==. (Just $ entityKey ent)] []
2016-09-05 15:17:57 +00:00
mapM_ (\child -> do
-- delete comment children
runDB $ delete $ entityKey child
) children
runDB $ delete $ entityKey ent) commEnts
2014-12-27 22:09:51 +00:00
-- delete media files
medium <- runDB $ getJust med
liftIO $ removeFile (normalise $ L.tail $ mediumPath medium)
liftIO $ removeFile (normalise $ L.tail $ mediumThumb medium)
2016-05-04 00:26:48 +00:00
liftIO $ removeFile (normalise $ L.tail $ mediumPreview medium)
-- delete medium database entry and search
2014-12-27 22:09:51 +00:00
runDB $ delete med
) mediaList
runDB $ delete albumId
) albumList
runDB $ delete ownerId
2015-09-14 16:54:46 +00:00
liftIO $ removeDirectoryRecursive $ "static" </> "data" </> T.unpack (extractKey ownerId)
2014-12-27 22:09:51 +00:00
setMessage "User successfully deleted"
2015-09-14 16:54:46 +00:00
redirect AdminR
2014-12-27 22:09:51 +00:00
Nothing -> do
setMessage "This user 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