condensing code in admin interface
This commit is contained in:
parent
70ca625585
commit
4b81a54503
8 changed files with 372 additions and 472 deletions
|
@ -60,6 +60,7 @@ import Handler.AdminMediumSettings
|
||||||
import Handler.AdminComments
|
import Handler.AdminComments
|
||||||
import Handler.Tag
|
import Handler.Tag
|
||||||
import Handler.RootFeed
|
import Handler.RootFeed
|
||||||
|
import Handler.Commons
|
||||||
|
|
||||||
-- This line actually creates our YesodDispatch instance. It is the second half
|
-- This line actually creates our YesodDispatch instance. It is the second half
|
||||||
-- of the call to mkYesodData which occurs in Foundation.hs. Please see the
|
-- of the call to mkYesodData which occurs in Foundation.hs. Please see the
|
||||||
|
|
|
@ -1,22 +1,16 @@
|
||||||
module Handler.Admin where
|
module Handler.Admin where
|
||||||
|
|
||||||
import Import
|
import Import
|
||||||
|
import Handler.Commons
|
||||||
|
|
||||||
getAdminR :: Handler Html
|
getAdminR :: Handler Html
|
||||||
getAdminR = do
|
getAdminR = do
|
||||||
msu <- lookupSession "userId"
|
adminCheck <- loginIsAdmin
|
||||||
case msu of
|
case adminCheck of
|
||||||
Just tempUserId -> do
|
Right _ -> do
|
||||||
userId <- return $ getUserIdFromText tempUserId
|
|
||||||
user <- runDB $ getJust userId
|
|
||||||
case userAdmin user of
|
|
||||||
True -> do
|
|
||||||
defaultLayout $ do
|
defaultLayout $ do
|
||||||
setTitle "Administration: Menu"
|
setTitle "Administration: Menu"
|
||||||
$(widgetFile "adminBase")
|
$(widgetFile "adminBase")
|
||||||
False -> do
|
Left (errorMsg, route) -> do
|
||||||
setMessage "You have no admin rights"
|
setMessage errorMsg
|
||||||
redirect $ HomeR
|
redirect $ route
|
||||||
Nothing -> do
|
|
||||||
setMessage "You are not logged in"
|
|
||||||
redirect $ LoginR
|
|
||||||
|
|
|
@ -1,6 +1,7 @@
|
||||||
module Handler.AdminAlbumSettings where
|
module Handler.AdminAlbumSettings where
|
||||||
|
|
||||||
import Import
|
import Import
|
||||||
|
import Handler.Commons
|
||||||
import qualified Data.Text as T
|
import qualified Data.Text as T
|
||||||
import qualified Data.List as L
|
import qualified Data.List as L
|
||||||
import System.FilePath
|
import System.FilePath
|
||||||
|
@ -8,33 +9,22 @@ import System.Directory
|
||||||
|
|
||||||
getAdminAlbumsR :: Handler Html
|
getAdminAlbumsR :: Handler Html
|
||||||
getAdminAlbumsR = do
|
getAdminAlbumsR = do
|
||||||
msu <- lookupSession "userId"
|
adminCheck <- loginIsAdmin
|
||||||
case msu of
|
case adminCheck of
|
||||||
Just tempUserId -> do
|
Right _ -> do
|
||||||
userId <- return $ getUserIdFromText tempUserId
|
|
||||||
user <- runDB $ getJust userId
|
|
||||||
case userAdmin user of
|
|
||||||
True -> do
|
|
||||||
albums <- runDB $ selectList [] [Asc AlbumTitle]
|
albums <- runDB $ selectList [] [Asc AlbumTitle]
|
||||||
defaultLayout $ do
|
defaultLayout $ do
|
||||||
setTitle "Administration: Albums"
|
setTitle "Administration: Albums"
|
||||||
$(widgetFile "adminAlbums")
|
$(widgetFile "adminAlbums")
|
||||||
False -> do
|
Left (errorMsg, route) -> do
|
||||||
setMessage "You are no admin"
|
setMessage errorMsg
|
||||||
redirect $ HomeR
|
redirect $ route
|
||||||
Nothing -> do
|
|
||||||
setMessage "You must be logged in"
|
|
||||||
redirect $ LoginR
|
|
||||||
|
|
||||||
getAdminAlbumMediaR :: AlbumId -> Handler Html
|
getAdminAlbumMediaR :: AlbumId -> Handler Html
|
||||||
getAdminAlbumMediaR albumId = do
|
getAdminAlbumMediaR albumId = do
|
||||||
msu <- lookupSession "userId"
|
adminCheck <- loginIsAdmin
|
||||||
case msu of
|
case adminCheck of
|
||||||
Just tempUserId -> do
|
Right _ -> do
|
||||||
userId <- return $ getUserIdFromText tempUserId
|
|
||||||
user <- runDB $ getJust userId
|
|
||||||
case userAdmin user of
|
|
||||||
True -> do
|
|
||||||
tempAlbum <- runDB $ get albumId
|
tempAlbum <- runDB $ get albumId
|
||||||
case tempAlbum of
|
case tempAlbum of
|
||||||
Just album -> do
|
Just album -> do
|
||||||
|
@ -45,22 +35,15 @@ getAdminAlbumMediaR albumId = do
|
||||||
Nothing -> do
|
Nothing -> do
|
||||||
setMessage "This album does not exist"
|
setMessage "This album does not exist"
|
||||||
redirect $ AdminR
|
redirect $ AdminR
|
||||||
False -> do
|
Left (errorMsg, route) -> do
|
||||||
setMessage "You are no admin"
|
setMessage errorMsg
|
||||||
redirect $ HomeR
|
redirect $ route
|
||||||
Nothing -> do
|
|
||||||
setMessage "You must be logged in"
|
|
||||||
redirect $ LoginR
|
|
||||||
|
|
||||||
getAdminAlbumSettingsR :: AlbumId -> Handler Html
|
getAdminAlbumSettingsR :: AlbumId -> Handler Html
|
||||||
getAdminAlbumSettingsR albumId = do
|
getAdminAlbumSettingsR albumId = do
|
||||||
msu <- lookupSession "userId"
|
adminCheck <- loginIsAdmin
|
||||||
case msu of
|
case adminCheck of
|
||||||
Just tempUserId -> do
|
Right _ -> do
|
||||||
userId <- return $ getUserIdFromText tempUserId
|
|
||||||
user <- runDB $ getJust userId
|
|
||||||
case userAdmin user of
|
|
||||||
True -> do
|
|
||||||
tempAlbum <- runDB $ get albumId
|
tempAlbum <- runDB $ get albumId
|
||||||
case tempAlbum of
|
case tempAlbum of
|
||||||
Just album -> do
|
Just album -> do
|
||||||
|
@ -73,22 +56,15 @@ getAdminAlbumSettingsR albumId = do
|
||||||
Nothing -> do
|
Nothing -> do
|
||||||
setMessage "This album does not exist"
|
setMessage "This album does not exist"
|
||||||
redirect $ AdminR
|
redirect $ AdminR
|
||||||
False -> do
|
Left (errorMsg, route) -> do
|
||||||
setMessage "You are no admin"
|
setMessage errorMsg
|
||||||
redirect $ HomeR
|
redirect $ route
|
||||||
Nothing -> do
|
|
||||||
setMessage "You must be logged in"
|
|
||||||
redirect $ LoginR
|
|
||||||
|
|
||||||
postAdminAlbumSettingsR :: AlbumId -> Handler Html
|
postAdminAlbumSettingsR :: AlbumId -> Handler Html
|
||||||
postAdminAlbumSettingsR albumId = do
|
postAdminAlbumSettingsR albumId = do
|
||||||
msu <- lookupSession "userId"
|
adminCheck <- loginIsAdmin
|
||||||
case msu of
|
case adminCheck of
|
||||||
Just tempUserId -> do
|
Right _ -> do
|
||||||
userId <- return $ getUserIdFromText tempUserId
|
|
||||||
user <- runDB $ getJust userId
|
|
||||||
case userAdmin user of
|
|
||||||
True -> do
|
|
||||||
tempAlbum <- runDB $ get albumId
|
tempAlbum <- runDB $ get albumId
|
||||||
case tempAlbum of
|
case tempAlbum of
|
||||||
Just album -> do
|
Just album -> do
|
||||||
|
@ -110,12 +86,9 @@ postAdminAlbumSettingsR albumId = do
|
||||||
Nothing -> do
|
Nothing -> do
|
||||||
setMessage "This album does not exist"
|
setMessage "This album does not exist"
|
||||||
redirect $ AdminR
|
redirect $ AdminR
|
||||||
False -> do
|
Left (errorMsg, route) -> do
|
||||||
setMessage "You are no admin"
|
setMessage errorMsg
|
||||||
redirect $ HomeR
|
redirect $ route
|
||||||
Nothing -> do
|
|
||||||
setMessage "You must be logged in"
|
|
||||||
redirect $ LoginR
|
|
||||||
|
|
||||||
adminAlbumSettingsForm :: Album -> AlbumId -> [(Text, UserId)] -> Form Album
|
adminAlbumSettingsForm :: Album -> AlbumId -> [(Text, UserId)] -> Form Album
|
||||||
adminAlbumSettingsForm album albumId users = renderDivs $ Album
|
adminAlbumSettingsForm album albumId users = renderDivs $ Album
|
||||||
|
@ -128,19 +101,12 @@ adminAlbumSettingsForm album albumId users = renderDivs $ Album
|
||||||
media = do
|
media = do
|
||||||
entities <- runDB $ selectList [MediumAlbum ==. albumId] [Asc MediumTitle]
|
entities <- runDB $ selectList [MediumAlbum ==. albumId] [Asc MediumTitle]
|
||||||
optionsPairs $ map (\med -> (mediumTitle $ entityVal med, mediumThumb (entityVal med))) entities
|
optionsPairs $ map (\med -> (mediumTitle $ entityVal med, mediumThumb (entityVal med))) entities
|
||||||
-- userNames =
|
|
||||||
-- let entities = runDB $ selectList [UserId !=. (albumOwner album)] [Desc UserName]
|
|
||||||
-- in map (\ent -> (userName $ entityVal ent, entityKey ent)) entities
|
|
||||||
|
|
||||||
getAdminAlbumDeleteR :: AlbumId -> Handler Html
|
getAdminAlbumDeleteR :: AlbumId -> Handler Html
|
||||||
getAdminAlbumDeleteR albumId = do
|
getAdminAlbumDeleteR albumId = do
|
||||||
msu <- lookupSession "userId"
|
adminCheck <- loginIsAdmin
|
||||||
case msu of
|
case adminCheck of
|
||||||
Just tempUserId -> do
|
Right _ -> do
|
||||||
userId <- return $ getUserIdFromText tempUserId
|
|
||||||
user <- runDB $ getJust userId
|
|
||||||
case userAdmin user of
|
|
||||||
True -> do
|
|
||||||
tempAlbum <- runDB $ get albumId
|
tempAlbum <- runDB $ get albumId
|
||||||
case tempAlbum of
|
case tempAlbum of
|
||||||
Just album -> do
|
Just album -> do
|
||||||
|
@ -172,9 +138,6 @@ getAdminAlbumDeleteR albumId = do
|
||||||
Nothing -> do
|
Nothing -> do
|
||||||
setMessage "This album dies not exist"
|
setMessage "This album dies not exist"
|
||||||
redirect $ AdminR
|
redirect $ AdminR
|
||||||
False -> do
|
Left (errorMsg, route) -> do
|
||||||
setMessage "You are no admin"
|
setMessage errorMsg
|
||||||
redirect $ HomeR
|
redirect $ route
|
||||||
Nothing -> do
|
|
||||||
setMessage "You must be logged in"
|
|
||||||
redirect $ LoginR
|
|
||||||
|
|
|
@ -1,41 +1,31 @@
|
||||||
module Handler.AdminComments where
|
module Handler.AdminComments where
|
||||||
|
|
||||||
import Import
|
import Import
|
||||||
|
import Handler.Commons
|
||||||
import Data.Maybe
|
import Data.Maybe
|
||||||
import Data.Time
|
import Data.Time
|
||||||
import System.Locale
|
import System.Locale
|
||||||
|
|
||||||
getAdminCommentR :: Handler Html
|
getAdminCommentR :: Handler Html
|
||||||
getAdminCommentR = do
|
getAdminCommentR = do
|
||||||
msu <- lookupSession "userId"
|
adminCheck <- loginIsAdmin
|
||||||
case msu of
|
case adminCheck of
|
||||||
Just tempUserId -> do
|
Right _ -> do
|
||||||
userId <- return $ getUserIdFromText tempUserId
|
|
||||||
user <- runDB $ getJust userId
|
|
||||||
case userAdmin user of
|
|
||||||
True -> do
|
|
||||||
media <- runDB $ selectList [] [Desc MediumTime]
|
media <- runDB $ selectList [] [Desc MediumTime]
|
||||||
comments <- runDB $ selectList [CommentParent ==. Nothing] [Desc CommentTime]
|
comments <- runDB $ selectList [CommentParent ==. Nothing] [Desc CommentTime]
|
||||||
replies <- runDB $ selectList [CommentParent !=. Nothing] [Desc CommentTime]
|
replies <- runDB $ selectList [CommentParent !=. Nothing] [Desc CommentTime]
|
||||||
defaultLayout $ do
|
defaultLayout $ do
|
||||||
setTitle "Administration: Comments"
|
setTitle "Administration: Comments"
|
||||||
$(widgetFile "adminComments")
|
$(widgetFile "adminComments")
|
||||||
False -> do
|
Left (errorMsg, route) -> do
|
||||||
setMessage "You have no admin rights"
|
setMessage errorMsg
|
||||||
redirect $ HomeR
|
redirect $ route
|
||||||
Nothing -> do
|
|
||||||
setMessage "You are not logged in"
|
|
||||||
redirect $ LoginR
|
|
||||||
|
|
||||||
getAdminCommentDeleteR :: CommentId -> Handler Html
|
getAdminCommentDeleteR :: CommentId -> Handler Html
|
||||||
getAdminCommentDeleteR commentId = do
|
getAdminCommentDeleteR commentId = do
|
||||||
msu <- lookupSession "userId"
|
adminCheck <- loginIsAdmin
|
||||||
case msu of
|
case adminCheck of
|
||||||
Just tempUserId -> do
|
Right _ -> do
|
||||||
userId <- return $ getUserIdFromText tempUserId
|
|
||||||
user <- runDB $ getJust userId
|
|
||||||
case userAdmin user of
|
|
||||||
True -> do
|
|
||||||
tempComment <- runDB $ get commentId
|
tempComment <- runDB $ get commentId
|
||||||
case tempComment of
|
case tempComment of
|
||||||
Just comment -> do
|
Just comment -> do
|
||||||
|
@ -49,9 +39,6 @@ getAdminCommentDeleteR commentId = do
|
||||||
Nothing -> do
|
Nothing -> do
|
||||||
setMessage "This comment does not exist"
|
setMessage "This comment does not exist"
|
||||||
redirect $ AdminR
|
redirect $ AdminR
|
||||||
False -> do
|
Left (errorMsg, route) -> do
|
||||||
setMessage "You are no admin"
|
setMessage errorMsg
|
||||||
redirect $ HomeR
|
redirect $ route
|
||||||
Nothing -> do
|
|
||||||
setMessage "You must be logged in"
|
|
||||||
redirect $ LoginR
|
|
||||||
|
|
|
@ -1,39 +1,29 @@
|
||||||
module Handler.AdminMediumSettings where
|
module Handler.AdminMediumSettings where
|
||||||
|
|
||||||
import Import
|
import Import
|
||||||
|
import Handler.Commons
|
||||||
import System.FilePath
|
import System.FilePath
|
||||||
import System.Directory
|
import System.Directory
|
||||||
import Data.List (tail)
|
import Data.List (tail)
|
||||||
|
|
||||||
getAdminMediaR :: Handler Html
|
getAdminMediaR :: Handler Html
|
||||||
getAdminMediaR = do
|
getAdminMediaR = do
|
||||||
msu <- lookupSession "userId"
|
adminCheck <- loginIsAdmin
|
||||||
case msu of
|
case adminCheck of
|
||||||
Just tempUserId -> do
|
Right _ -> do
|
||||||
userId <- return $ getUserIdFromText tempUserId
|
|
||||||
user <- runDB $ getJust userId
|
|
||||||
case userAdmin user of
|
|
||||||
True -> do
|
|
||||||
media <- runDB $ selectList [] [Asc MediumTitle]
|
media <- runDB $ selectList [] [Asc MediumTitle]
|
||||||
defaultLayout $ do
|
defaultLayout $ do
|
||||||
setTitle "Administration: Media"
|
setTitle "Administration: Media"
|
||||||
$(widgetFile "adminMedia")
|
$(widgetFile "adminMedia")
|
||||||
False -> do
|
Left (errorMsg, route) -> do
|
||||||
setMessage "You are no admin"
|
setMessage errorMsg
|
||||||
redirect $ HomeR
|
redirect $ route
|
||||||
Nothing -> do
|
|
||||||
setMessage "You must be logged in"
|
|
||||||
redirect $ LoginR
|
|
||||||
|
|
||||||
getAdminMediumSettingsR :: MediumId -> Handler Html
|
getAdminMediumSettingsR :: MediumId -> Handler Html
|
||||||
getAdminMediumSettingsR mediumId = do
|
getAdminMediumSettingsR mediumId = do
|
||||||
msu <- lookupSession "userId"
|
adminCheck <- loginIsAdmin
|
||||||
case msu of
|
case adminCheck of
|
||||||
Just tempUserId -> do
|
Right _ -> do
|
||||||
userId <- return $ getUserIdFromText tempUserId
|
|
||||||
user <- runDB $ getJust userId
|
|
||||||
case userAdmin user of
|
|
||||||
True -> do
|
|
||||||
tempMedium <- runDB $ get mediumId
|
tempMedium <- runDB $ get mediumId
|
||||||
case tempMedium of
|
case tempMedium of
|
||||||
Just medium -> do
|
Just medium -> do
|
||||||
|
@ -44,22 +34,15 @@ getAdminMediumSettingsR mediumId = do
|
||||||
Nothing -> do
|
Nothing -> do
|
||||||
setMessage "This medium does not exist"
|
setMessage "This medium does not exist"
|
||||||
redirect $ AdminR
|
redirect $ AdminR
|
||||||
False -> do
|
Left (errorMsg, route) -> do
|
||||||
setMessage "You are no admin"
|
setMessage errorMsg
|
||||||
redirect $ HomeR
|
redirect $ route
|
||||||
Nothing -> do
|
|
||||||
setMessage "You must be logged in"
|
|
||||||
redirect $ LoginR
|
|
||||||
|
|
||||||
postAdminMediumSettingsR :: MediumId -> Handler Html
|
postAdminMediumSettingsR :: MediumId -> Handler Html
|
||||||
postAdminMediumSettingsR mediumId = do
|
postAdminMediumSettingsR mediumId = do
|
||||||
msu <- lookupSession "userId"
|
adminCheck <- loginIsAdmin
|
||||||
case msu of
|
case adminCheck of
|
||||||
Just tempUserId -> do
|
Right _ -> do
|
||||||
userId <- return $ getUserIdFromText tempUserId
|
|
||||||
user <- runDB $ getJust userId
|
|
||||||
case userAdmin user of
|
|
||||||
True -> do
|
|
||||||
tempMedium <- runDB $ get mediumId
|
tempMedium <- runDB $ get mediumId
|
||||||
case tempMedium of
|
case tempMedium of
|
||||||
Just medium -> do
|
Just medium -> do
|
||||||
|
@ -79,12 +62,9 @@ postAdminMediumSettingsR mediumId = do
|
||||||
Nothing -> do
|
Nothing -> do
|
||||||
setMessage "This medium does not exist"
|
setMessage "This medium does not exist"
|
||||||
redirect $ AdminR
|
redirect $ AdminR
|
||||||
False -> do
|
Left (errorMsg, route) -> do
|
||||||
setMessage "You are no admin"
|
setMessage errorMsg
|
||||||
redirect $ HomeR
|
redirect $ route
|
||||||
Nothing -> do
|
|
||||||
setMessage "You must be logged in"
|
|
||||||
redirect $ LoginR
|
|
||||||
|
|
||||||
adminMediumSetForm :: Medium -> Form Medium
|
adminMediumSetForm :: Medium -> Form Medium
|
||||||
adminMediumSetForm medium = renderDivs $ Medium
|
adminMediumSetForm medium = renderDivs $ Medium
|
||||||
|
@ -100,13 +80,9 @@ adminMediumSetForm medium = renderDivs $ Medium
|
||||||
|
|
||||||
getAdminMediumDeleteR :: MediumId -> Handler Html
|
getAdminMediumDeleteR :: MediumId -> Handler Html
|
||||||
getAdminMediumDeleteR mediumId = do
|
getAdminMediumDeleteR mediumId = do
|
||||||
msu <- lookupSession "userId"
|
adminCheck <- loginIsAdmin
|
||||||
case msu of
|
case adminCheck of
|
||||||
Just tempUserId -> do
|
Right _ -> do
|
||||||
userId <- return $ getUserIdFromText tempUserId
|
|
||||||
user <- runDB $ getJust userId
|
|
||||||
case userAdmin user of
|
|
||||||
True -> do
|
|
||||||
tempMedium <- runDB $ get mediumId
|
tempMedium <- runDB $ get mediumId
|
||||||
case tempMedium of
|
case tempMedium of
|
||||||
Just medium -> do
|
Just medium -> do
|
||||||
|
@ -130,9 +106,6 @@ getAdminMediumDeleteR mediumId = do
|
||||||
Nothing -> do
|
Nothing -> do
|
||||||
setMessage "This medium does not exist"
|
setMessage "This medium does not exist"
|
||||||
redirect $ AdminR
|
redirect $ AdminR
|
||||||
False -> do
|
Left (errorMsg, route) -> do
|
||||||
setMessage "You are no admin"
|
setMessage errorMsg
|
||||||
redirect $ HomeR
|
redirect $ route
|
||||||
Nothing -> do
|
|
||||||
setMessage "You must be logged in"
|
|
||||||
redirect $ LoginR
|
|
||||||
|
|
|
@ -1,40 +1,31 @@
|
||||||
module Handler.AdminProfileSettings where
|
module Handler.AdminProfileSettings where
|
||||||
|
|
||||||
import Import
|
import Import
|
||||||
|
import Handler.Commons
|
||||||
import qualified Data.Text as T
|
import qualified Data.Text as T
|
||||||
import qualified Data.List as L
|
import qualified Data.List as L
|
||||||
|
import Data.Maybe
|
||||||
import System.Directory
|
import System.Directory
|
||||||
import System.FilePath
|
import System.FilePath
|
||||||
|
|
||||||
getAdminProfilesR :: Handler Html
|
getAdminProfilesR :: Handler Html
|
||||||
getAdminProfilesR = do
|
getAdminProfilesR = do
|
||||||
msu <- lookupSession "userId"
|
adminCheck <- loginIsAdmin
|
||||||
case msu of
|
case adminCheck of
|
||||||
Just tempUserId -> do
|
Right _ -> do
|
||||||
userId <- return $ getUserIdFromText tempUserId
|
|
||||||
user <- runDB $ getJust userId
|
|
||||||
case userAdmin user of
|
|
||||||
True -> do
|
|
||||||
profiles <- runDB $ selectList [] [Desc UserName]
|
profiles <- runDB $ selectList [] [Desc UserName]
|
||||||
defaultLayout $ do
|
defaultLayout $ do
|
||||||
setTitle "Administration: Profiles"
|
setTitle "Administration: Profiles"
|
||||||
$(widgetFile "adminProfiles")
|
$(widgetFile "adminProfiles")
|
||||||
False -> do
|
Left (errorMsg, route) -> do
|
||||||
setMessage "You are no admin"
|
setMessage errorMsg
|
||||||
redirect $ HomeR
|
redirect $ route
|
||||||
Nothing -> do
|
|
||||||
setMessage "You must be logged in"
|
|
||||||
redirect $ LoginR
|
|
||||||
|
|
||||||
getAdminUserAlbumsR :: UserId -> Handler Html
|
getAdminUserAlbumsR :: UserId -> Handler Html
|
||||||
getAdminUserAlbumsR ownerId = do
|
getAdminUserAlbumsR ownerId = do
|
||||||
msu <- lookupSession "userId"
|
adminCheck <- loginIsAdmin
|
||||||
case msu of
|
case adminCheck of
|
||||||
Just tempUserId -> do
|
Right _ -> do
|
||||||
userId <- return $ getUserIdFromText tempUserId
|
|
||||||
user <- runDB $ getJust userId
|
|
||||||
case userAdmin user of
|
|
||||||
True -> do
|
|
||||||
tempOwner <- runDB $ get ownerId
|
tempOwner <- runDB $ get ownerId
|
||||||
case tempOwner of
|
case tempOwner of
|
||||||
Just owner -> do
|
Just owner -> do
|
||||||
|
@ -45,22 +36,15 @@ getAdminUserAlbumsR ownerId = do
|
||||||
Nothing -> do
|
Nothing -> do
|
||||||
setMessage "This user does not exist"
|
setMessage "This user does not exist"
|
||||||
redirect $ AdminR
|
redirect $ AdminR
|
||||||
False -> do
|
Left (errorMsg, route) -> do
|
||||||
setMessage "You are no admin"
|
setMessage errorMsg
|
||||||
redirect $ HomeR
|
redirect $ route
|
||||||
Nothing -> do
|
|
||||||
setMessage "You must be logged in"
|
|
||||||
redirect $ LoginR
|
|
||||||
|
|
||||||
getAdminUserMediaR :: UserId -> Handler Html
|
getAdminUserMediaR :: UserId -> Handler Html
|
||||||
getAdminUserMediaR ownerId = do
|
getAdminUserMediaR ownerId = do
|
||||||
msu <- lookupSession "userId"
|
adminCheck <- loginIsAdmin
|
||||||
case msu of
|
case adminCheck of
|
||||||
Just tempUserId -> do
|
Right _ -> do
|
||||||
userId <- return $ getUserIdFromText tempUserId
|
|
||||||
user <- runDB $ getJust userId
|
|
||||||
case userAdmin user of
|
|
||||||
True -> do
|
|
||||||
tempOwner <- runDB $ get ownerId
|
tempOwner <- runDB $ get ownerId
|
||||||
case tempOwner of
|
case tempOwner of
|
||||||
Just owner -> do
|
Just owner -> do
|
||||||
|
@ -71,25 +55,20 @@ getAdminUserMediaR ownerId = do
|
||||||
Nothing -> do
|
Nothing -> do
|
||||||
setMessage "This user does not exist"
|
setMessage "This user does not exist"
|
||||||
redirect $ AdminR
|
redirect $ AdminR
|
||||||
False -> do
|
Left (errorMsg, route) -> do
|
||||||
setMessage "You are no admin"
|
setMessage errorMsg
|
||||||
redirect $ HomeR
|
redirect $ route
|
||||||
Nothing -> do
|
|
||||||
setMessage "You must be logged in"
|
|
||||||
redirect $ LoginR
|
|
||||||
|
|
||||||
getAdminProfileSettingsR :: UserId -> Handler Html
|
getAdminProfileSettingsR :: UserId -> Handler Html
|
||||||
getAdminProfileSettingsR ownerId = do
|
getAdminProfileSettingsR ownerId = do
|
||||||
msu <- lookupSession "userId"
|
adminCheck <- loginIsAdmin
|
||||||
case msu of
|
case adminCheck of
|
||||||
Just tempUserId -> do
|
Right _ -> do
|
||||||
userId <- return $ getUserIdFromText tempUserId
|
|
||||||
user <- runDB $ getJust userId
|
|
||||||
case userAdmin user of
|
|
||||||
True -> do
|
|
||||||
tempOwner <- runDB $ get ownerId
|
tempOwner <- runDB $ get ownerId
|
||||||
case tempOwner of
|
case tempOwner of
|
||||||
Just owner -> do
|
Just owner -> do
|
||||||
|
tempUserId <- lookupSession "userId"
|
||||||
|
userId <- return $ getUserIdFromText $ fromJust tempUserId
|
||||||
(adminProfileSetWidget, enctype) <- generateFormPost $ adminProfileForm owner
|
(adminProfileSetWidget, enctype) <- generateFormPost $ adminProfileForm owner
|
||||||
defaultLayout $ do
|
defaultLayout $ do
|
||||||
setTitle "Administration: Profile settings"
|
setTitle "Administration: Profile settings"
|
||||||
|
@ -97,23 +76,15 @@ getAdminProfileSettingsR ownerId = do
|
||||||
Nothing -> do
|
Nothing -> do
|
||||||
setMessage "This user does not exist"
|
setMessage "This user does not exist"
|
||||||
redirect $ AdminR
|
redirect $ AdminR
|
||||||
False -> do
|
Left (errorMsg, route) -> do
|
||||||
setMessage "You are not an admin"
|
setMessage errorMsg
|
||||||
redirect $ HomeR
|
redirect $ route
|
||||||
Nothing -> do
|
|
||||||
setMessage "You are not logged in"
|
|
||||||
redirect $ LoginR
|
|
||||||
|
|
||||||
|
|
||||||
postAdminProfileSettingsR :: UserId -> Handler Html
|
postAdminProfileSettingsR :: UserId -> Handler Html
|
||||||
postAdminProfileSettingsR ownerId = do
|
postAdminProfileSettingsR ownerId = do
|
||||||
msu <- lookupSession "userId"
|
adminCheck <- loginIsAdmin
|
||||||
case msu of
|
case adminCheck of
|
||||||
Just tempUserId -> do
|
Right _ -> do
|
||||||
userId <- return $ getUserIdFromText tempUserId
|
|
||||||
user <- runDB $ getJust userId
|
|
||||||
case userAdmin user of
|
|
||||||
True -> do
|
|
||||||
tempOwner <- runDB $ get ownerId
|
tempOwner <- runDB $ get ownerId
|
||||||
case tempOwner of
|
case tempOwner of
|
||||||
Just owner -> do
|
Just owner -> do
|
||||||
|
@ -134,12 +105,9 @@ postAdminProfileSettingsR ownerId = do
|
||||||
Nothing -> do
|
Nothing -> do
|
||||||
setMessage "This user does not exist"
|
setMessage "This user does not exist"
|
||||||
redirect $ AdminR
|
redirect $ AdminR
|
||||||
False -> do
|
Left (errorMsg, route) -> do
|
||||||
setMessage "You are not an admin"
|
setMessage errorMsg
|
||||||
redirect $ HomeR
|
redirect $ route
|
||||||
Nothing -> do
|
|
||||||
setMessage "You are not logged in"
|
|
||||||
redirect $ LoginR
|
|
||||||
|
|
||||||
|
|
||||||
adminProfileForm :: User -> Form User
|
adminProfileForm :: User -> Form User
|
||||||
|
@ -154,13 +122,9 @@ adminProfileForm owner = renderDivs $ User
|
||||||
|
|
||||||
getAdminProfileDeleteR :: UserId -> Handler Html
|
getAdminProfileDeleteR :: UserId -> Handler Html
|
||||||
getAdminProfileDeleteR ownerId = do
|
getAdminProfileDeleteR ownerId = do
|
||||||
msu <- lookupSession "userId"
|
adminCheck <- loginIsAdmin
|
||||||
case msu of
|
case adminCheck of
|
||||||
Just tempUserId -> do
|
Right _ -> do
|
||||||
userId <- return $ getUserIdFromText tempUserId
|
|
||||||
user <- runDB $ getJust userId
|
|
||||||
case userAdmin user of
|
|
||||||
True -> do
|
|
||||||
tempOwner <- runDB $ get ownerId
|
tempOwner <- runDB $ get ownerId
|
||||||
case tempOwner of
|
case tempOwner of
|
||||||
Just owner -> do
|
Just owner -> do
|
||||||
|
@ -188,9 +152,6 @@ getAdminProfileDeleteR ownerId = do
|
||||||
Nothing -> do
|
Nothing -> do
|
||||||
setMessage "This user does not exist"
|
setMessage "This user does not exist"
|
||||||
redirect $ AdminR
|
redirect $ AdminR
|
||||||
False -> do
|
Left (errorMsg, route) -> do
|
||||||
setMessage "You are no admin"
|
setMessage errorMsg
|
||||||
redirect $ HomeR
|
redirect $ route
|
||||||
Nothing -> do
|
|
||||||
setMessage "You must be logged in"
|
|
||||||
redirect $ LoginR
|
|
||||||
|
|
20
Handler/Commons.hs
Normal file
20
Handler/Commons.hs
Normal file
|
@ -0,0 +1,20 @@
|
||||||
|
module Handler.Commons where
|
||||||
|
|
||||||
|
import Import
|
||||||
|
import Yesod
|
||||||
|
import Data.String
|
||||||
|
|
||||||
|
loginIsAdmin :: IsString t => Handler (Either (t, Route App) ())
|
||||||
|
loginIsAdmin = do
|
||||||
|
msu <- lookupSession "userId"
|
||||||
|
case msu of
|
||||||
|
Just tempUserId -> do
|
||||||
|
userId <- return $ getUserIdFromText tempUserId
|
||||||
|
user <- runDB $ getJust userId
|
||||||
|
case userAdmin user of
|
||||||
|
True ->
|
||||||
|
return $ Right ()
|
||||||
|
False ->
|
||||||
|
return $ Left ("You have no admin rights", HomeR)
|
||||||
|
Nothing ->
|
||||||
|
return $ Left ("You are not logged in", LoginR)
|
|
@ -41,6 +41,7 @@ library
|
||||||
Handler.AdminComments
|
Handler.AdminComments
|
||||||
Handler.Tag
|
Handler.Tag
|
||||||
Handler.RootFeed
|
Handler.RootFeed
|
||||||
|
Handler.Commons
|
||||||
|
|
||||||
if flag(dev) || flag(library-only)
|
if flag(dev) || flag(library-only)
|
||||||
cpp-options: -DDEVELOPMENT
|
cpp-options: -DDEVELOPMENT
|
||||||
|
|
Loading…
Reference in a new issue