2015-08-09 19:16:33 +00:00
|
|
|
-- yammat - Yet Another MateMAT
|
|
|
|
-- 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
|
|
|
|
-- along with this program. If not, see <http://www.gnu.org/licenses/>.
|
2017-06-03 01:00:04 +00:00
|
|
|
{-# LANGUAGE DoAndIfThenElse #-}
|
2015-04-04 04:46:33 +00:00
|
|
|
module Handler.NewUser where
|
|
|
|
|
2015-04-07 20:03:21 +00:00
|
|
|
import Import as I
|
2015-04-09 21:03:49 +00:00
|
|
|
import Handler.Common
|
|
|
|
import Text.Shakespeare.Text
|
2015-04-04 04:46:33 +00:00
|
|
|
|
|
|
|
getNewUserR :: Handler Html
|
|
|
|
getNewUserR = do
|
2017-06-03 01:00:04 +00:00
|
|
|
settings <- getsYesod appSettings
|
|
|
|
if appUserCreationBlocked settings
|
|
|
|
then do
|
|
|
|
setMessageI MsgCreationBlocked
|
|
|
|
redirect HomeR
|
|
|
|
else do
|
|
|
|
today <- liftIO $ return . utctDay =<< getCurrentTime
|
|
|
|
(newUserWidget, enctype) <- generateFormPost
|
|
|
|
$ renderBootstrap3 BootstrapBasicForm
|
|
|
|
$ newUserForm today
|
2018-09-04 16:06:12 +00:00
|
|
|
defaultLayout $ do
|
|
|
|
setTitleI MsgNewUser
|
2017-06-03 01:00:04 +00:00
|
|
|
$(widgetFile "newUser")
|
2015-04-04 04:46:33 +00:00
|
|
|
|
|
|
|
postNewUserR :: Handler Html
|
|
|
|
postNewUserR = do
|
2017-06-03 01:00:04 +00:00
|
|
|
settings <- getsYesod appSettings
|
|
|
|
if appUserCreationBlocked settings
|
|
|
|
then do
|
|
|
|
setMessageI MsgCreationBlocked
|
|
|
|
redirect HomeR
|
|
|
|
else do
|
|
|
|
today <- liftIO $ return . utctDay =<< getCurrentTime
|
|
|
|
((res, _), _) <- runFormPost
|
|
|
|
$ renderBootstrap3 BootstrapBasicForm
|
|
|
|
$ newUserForm today
|
|
|
|
case res of
|
|
|
|
FormSuccess user -> do
|
|
|
|
namesakes <- runDB $ selectList [UserIdent ==. userIdent user] []
|
|
|
|
if null namesakes
|
|
|
|
then do
|
|
|
|
runDB $ insert_ user
|
|
|
|
setMessageI MsgUserCreated
|
|
|
|
redirect HomeR
|
|
|
|
else do
|
|
|
|
setMessageI MsgUserIdentNotUnique
|
|
|
|
redirect NewUserR
|
|
|
|
_ -> do
|
|
|
|
setMessageI MsgUserNotCreated
|
|
|
|
redirect NewUserR
|
2015-04-04 04:46:33 +00:00
|
|
|
|
2016-03-17 22:59:52 +00:00
|
|
|
newUserForm :: Day -> AForm Handler User
|
|
|
|
newUserForm today = User
|
2015-10-22 21:57:27 +00:00
|
|
|
<$> areq textField (bfs MsgName) Nothing
|
2015-04-04 04:46:33 +00:00
|
|
|
<*> pure 0
|
2016-03-17 22:59:52 +00:00
|
|
|
<*> pure today
|
2015-10-22 21:57:27 +00:00
|
|
|
<*> aopt emailField (bfs MsgEmailNotify) Nothing
|
|
|
|
<*> aopt (selectField avatars) (bfs MsgSelectAvatar) Nothing
|
2018-10-02 18:25:32 +00:00
|
|
|
<*> aopt passwordField (bfs MsgUserPin) Nothing
|
2015-10-22 21:57:27 +00:00
|
|
|
<* bootstrapSubmit (msgToBSSubmit MsgSubmit)
|
2015-04-16 00:12:03 +00:00
|
|
|
where
|
|
|
|
avatars = do
|
|
|
|
ents <- runDB $ selectList [] [Asc AvatarIdent]
|
|
|
|
optionsPairs $ map (\ent -> ((avatarIdent $ entityVal ent), entityKey ent)) ents
|
2015-04-07 20:03:21 +00:00
|
|
|
|
|
|
|
data UserConf = UserConf
|
2015-10-26 17:33:34 +00:00
|
|
|
{ userConfIdent :: Text
|
|
|
|
, userConfEmail :: Maybe Text
|
2015-04-16 00:51:08 +00:00
|
|
|
, userConfAvatar :: Maybe AvatarId
|
2015-07-21 07:14:38 +00:00
|
|
|
, userConfBarcode :: Maybe [Text]
|
2018-10-02 18:25:32 +00:00
|
|
|
, userConfPIN :: Maybe Text
|
2015-04-07 20:03:21 +00:00
|
|
|
}
|
|
|
|
|
|
|
|
getModifyUserR :: UserId -> Handler Html
|
2016-05-23 18:35:14 +00:00
|
|
|
getModifyUserR uId =
|
|
|
|
isUser uId HomeR >>= (\user -> do
|
|
|
|
p <- lookupGetParam "barcode"
|
|
|
|
_ <- handleGetParam p (Left uId)
|
|
|
|
rawbs <- runDB $ selectList [BarcodeUser ==. Just uId] []
|
|
|
|
let bs = map (barcodeCode . entityVal) rawbs
|
|
|
|
(modifyUserWidget, enctype) <- generateFormPost
|
|
|
|
$ renderBootstrap3 BootstrapBasicForm
|
|
|
|
$ modifyUserForm user bs
|
2018-09-04 16:06:12 +00:00
|
|
|
defaultLayout $ do
|
2018-09-04 16:16:03 +00:00
|
|
|
setTitleI (MsgModifyUser (userIdent user))
|
2016-05-23 18:35:14 +00:00
|
|
|
$(widgetFile "modifyUser")
|
|
|
|
)
|
2015-04-07 20:03:21 +00:00
|
|
|
|
|
|
|
postModifyUserR :: UserId -> Handler Html
|
2016-05-23 18:35:14 +00:00
|
|
|
postModifyUserR uId =
|
|
|
|
isUser uId HomeR >>= (\user -> do
|
|
|
|
rawbs <- runDB $ selectList [BarcodeUser ==. Just uId] []
|
|
|
|
let bs = map (barcodeCode . entityVal) rawbs
|
|
|
|
((res, _), _) <- runFormPost
|
|
|
|
$ renderBootstrap3 BootstrapBasicForm
|
|
|
|
$ modifyUserForm user bs
|
|
|
|
case res of
|
|
|
|
FormSuccess uc -> do
|
|
|
|
namesakes <- runDB $ selectList [UserIdent ==. userConfIdent uc, UserId !=. uId] []
|
|
|
|
if null namesakes
|
|
|
|
then do
|
|
|
|
runDB $ update uId
|
|
|
|
[ UserIdent =. userConfIdent uc
|
|
|
|
, UserEmail =. userConfEmail uc
|
|
|
|
, UserAvatar =. userConfAvatar uc
|
2018-10-02 18:25:32 +00:00
|
|
|
, UserPin =. userConfPIN uc
|
2016-05-23 18:35:14 +00:00
|
|
|
]
|
|
|
|
liftIO $ notify user (userConfEmail uc)
|
|
|
|
handleBarcodes (Left uId) (fromMaybe [] $ userConfBarcode uc)
|
|
|
|
setMessageI MsgUserEdited
|
|
|
|
redirect $ SelectR uId
|
|
|
|
else do
|
|
|
|
setMessageI MsgUserIdentNotUnique
|
|
|
|
redirect $ ModifyUserR uId
|
|
|
|
_ -> do
|
|
|
|
setMessageI MsgUserNotEdited
|
|
|
|
redirect $ SelectR uId
|
|
|
|
)
|
2015-04-07 20:03:21 +00:00
|
|
|
|
2015-10-22 21:57:27 +00:00
|
|
|
modifyUserForm :: User -> [Text] -> AForm Handler UserConf
|
|
|
|
modifyUserForm user bs = UserConf
|
2015-10-26 17:33:34 +00:00
|
|
|
<$> areq textField (bfs MsgName) (Just $ userIdent user)
|
|
|
|
<*> aopt emailField (bfs MsgEmailNotify) (Just $ userEmail user)
|
2015-10-22 21:57:27 +00:00
|
|
|
<*> aopt (selectField avatars) (bfs MsgSelectAvatar) (Just $ userAvatar user)
|
|
|
|
<*> aopt barcodeField (bfs MsgBarcodeField) (Just $ Just bs)
|
2018-10-02 18:25:32 +00:00
|
|
|
<*> aopt passwordField (bfs MsgUserPin) Nothing
|
2015-10-22 21:57:27 +00:00
|
|
|
<* bootstrapSubmit (msgToBSSubmit MsgSubmit)
|
2015-04-16 00:51:08 +00:00
|
|
|
where
|
|
|
|
avatars = do
|
|
|
|
ents <- runDB $ selectList [] [Asc AvatarIdent]
|
|
|
|
optionsPairs $ map (\ent -> ((avatarIdent $ entityVal ent), entityKey ent)) ents
|
2015-04-09 21:03:49 +00:00
|
|
|
|
2015-04-10 15:00:19 +00:00
|
|
|
notify :: User -> Maybe Text -> IO ()
|
|
|
|
notify user email
|
|
|
|
| (userEmail user) == email = return ()
|
2015-04-09 21:18:47 +00:00
|
|
|
| otherwise = case userEmail user of
|
2015-04-10 15:00:19 +00:00
|
|
|
Just address -> sendMail address "Profiländerung"
|
2015-04-09 21:18:47 +00:00
|
|
|
[stext|
|
2015-04-09 21:03:49 +00:00
|
|
|
Hallo #{userIdent user},
|
|
|
|
|
|
|
|
deine Profileinstellungen wurden geändert.
|
|
|
|
Nur damit du Bescheid weißt.
|
|
|
|
|
|
|
|
Grüße,
|
|
|
|
|
|
|
|
der Matemat
|
2015-04-09 21:18:47 +00:00
|
|
|
|]
|
|
|
|
Nothing -> return ()
|