158 lines
6.0 KiB
Haskell
158 lines
6.0 KiB
Haskell
module Handler.Admin where
|
|
|
|
import Import
|
|
import Handler.Utils
|
|
import Jobs
|
|
|
|
import Data.Aeson.Encode.Pretty (encodePrettyToTextBuilder)
|
|
|
|
import Control.Monad.Trans.Except
|
|
|
|
-- import Data.Time
|
|
-- import qualified Data.Text as T
|
|
-- import Data.Function ((&))
|
|
-- import Yesod.Form.Bootstrap3
|
|
|
|
import Database.Persist.Sql (fromSqlKey)
|
|
|
|
-- import Colonnade hiding (fromMaybe)
|
|
-- import Yesod.Colonnade
|
|
|
|
-- import qualified Data.UUID.Cryptographic as UUID
|
|
|
|
-- BEGIN - Buttons needed only here
|
|
data ButtonCreate = CreateMath | CreateInf -- Dummy for Example
|
|
deriving (Enum, Eq, Ord, Bounded, Read, Show, Generic, Typeable)
|
|
instance Universe ButtonCreate
|
|
instance Finite ButtonCreate
|
|
|
|
nullaryPathPiece ''ButtonCreate camelToPathPiece
|
|
|
|
instance Button UniWorX ButtonCreate where
|
|
btnLabel CreateMath = [whamlet|Ma<i>thema</i>tik|]
|
|
btnLabel CreateInf = "Informatik"
|
|
|
|
btnClasses CreateMath = [BCIsButton, BCInfo]
|
|
btnClasses CreateInf = [BCIsButton, BCPrimary]
|
|
-- END Button needed here
|
|
|
|
emailTestForm :: AForm (HandlerT UniWorX IO) (Email, MailContext)
|
|
emailTestForm = (,)
|
|
<$> areq emailField (fslI MsgMailTestFormEmail) Nothing
|
|
<*> ( MailContext
|
|
<$> (MailLanguages <$> areq (reorderField appLanguagesOpts) (fslI MsgMailTestFormLanguages) Nothing)
|
|
<*> (toMailDateTimeFormat
|
|
<$> areq (selectField $ dateTimeFormatOptions SelFormatDateTime) (fslI MsgDateTimeFormat) Nothing
|
|
<*> areq (selectField $ dateTimeFormatOptions SelFormatDate) (fslI MsgDateFormat) Nothing
|
|
<*> areq (selectField $ dateTimeFormatOptions SelFormatTime) (fslI MsgTimeFormat) Nothing
|
|
)
|
|
)
|
|
<* submitButton
|
|
where
|
|
toMailDateTimeFormat dt d t = \case
|
|
SelFormatDateTime -> dt
|
|
SelFormatDate -> d
|
|
SelFormatTime -> t
|
|
|
|
makeDemoForm :: Int -> Form (Int,Bool,Double)
|
|
makeDemoForm n = identifyForm "adminTestForm" $ \html -> do -- Important: used identForm instead!
|
|
(result, widget) <- flip (renderAForm FormStandard) html $ (,,)
|
|
<$> areq (minIntField n "Zahl") (fromString $ "Ganzzahl > " ++ show n) Nothing
|
|
<* aformSection MsgFormBehaviour
|
|
<*> areq checkBoxField "Muss nächste Zahl größer sein?" (Just True)
|
|
<*> areq doubleField "Fliesskommazahl" Nothing
|
|
<* submitButton
|
|
return $ case result of
|
|
FormSuccess fsres
|
|
| errorMsgs <- validateResult fsres
|
|
, not $ null errorMsgs -> (FormFailure errorMsgs, widget)
|
|
_otherwise -> (result, widget)
|
|
where
|
|
validateResult :: (Int,Bool,Double) -> [Text]
|
|
validateResult (i,True,d) | fromIntegral i >= d = [tshow d <> " ist nicht größer als " <> tshow i, "Zweite Fehlermeldung", "Dritte Fehlermeldung"]
|
|
validateResult _other = []
|
|
|
|
|
|
getAdminTestR, postAdminTestR :: Handler Html -- Demo Page. Referenzimplementierungen sollte hier gezeigt werden!
|
|
getAdminTestR = postAdminTestR
|
|
postAdminTestR = do
|
|
((btnResult, btnWdgt), btnEnctype) <- runFormPost $ identifyForm "buttons" (buttonForm :: Form ButtonCreate)
|
|
case btnResult of
|
|
(FormSuccess CreateInf) -> addMessage Info "Informatik-Knopf gedrückt"
|
|
(FormSuccess CreateMath) -> addMessage Warning "Knopf Mathematik erkannt"
|
|
FormMissing -> return ()
|
|
_other -> addMessage Warning "KEIN Knopf erkannt"
|
|
|
|
((emailResult, emailWidget), emailEnctype) <- runFormPost . identifyForm "email" $ renderAForm FormStandard emailTestForm
|
|
case emailResult of
|
|
(FormSuccess (email, ls)) -> do
|
|
jId <- runDB $ do
|
|
jId <- queueJob $ JobSendTestEmail email ls
|
|
addMessage Success [shamlet|Email-test gestartet (Job ##{tshow (fromSqlKey jId)})|]
|
|
return jId
|
|
writeJobCtl $ JobCtlPerform jId
|
|
FormMissing -> return ()
|
|
(FormFailure errs) -> forM_ errs $ addMessage Error . toHtml
|
|
|
|
let emailWidget' = [whamlet|
|
|
<form method=post action=@{AdminTestR} enctype=#{emailEnctype} data-ajax-submit>
|
|
^{emailWidget}
|
|
|]
|
|
|
|
|
|
let demoFormAction (_i,_b,_d) = addMessage Info "All ok."
|
|
((demoResult, formWidget),formEnctype) <- runFormPost $ makeDemoForm 7
|
|
formResult demoResult demoFormAction
|
|
let actionUrl = AdminTestR
|
|
let showDemoResult = [whamlet|
|
|
$maybe (i,b,d) <- formResult' demoResult
|
|
Received values:
|
|
<ul>
|
|
<li>#{show i}
|
|
<li>#{show b}
|
|
<li>#{show d}
|
|
$nothing
|
|
No form values received, due to #
|
|
$# Using formResult' above means that we usually to not distinguish the following two cases here, sind formResult does this already:
|
|
$case demoResult
|
|
$of FormSuccess _
|
|
$# Already dealt with above, to showecase usage of formResult' as normally done.
|
|
success, which should not happen here.
|
|
$of FormMissing
|
|
Form data missing, probably empty.
|
|
$of FormFailure msgs
|
|
<ul>
|
|
$forall m <- msgs
|
|
<li>#{m}
|
|
|]
|
|
|
|
let locallyDefinedPageHeading = [whamlet|Admin TestPage for Uni2work|]
|
|
siteLayout locallyDefinedPageHeading $ do
|
|
-- defaultLayout $ do
|
|
setTitle "Uni2work Admin Testpage"
|
|
$(widgetFile "adminTest")
|
|
|
|
[whamlet|<h2>Formular Demonstration|]
|
|
$(widgetFile "formPage")
|
|
showDemoResult
|
|
|
|
|
|
getAdminErrMsgR, postAdminErrMsgR :: Handler Html
|
|
getAdminErrMsgR = postAdminErrMsgR
|
|
postAdminErrMsgR = do
|
|
((ctResult, ctView), ctEncoding) <- runFormPost . renderAForm FormStandard $
|
|
(unTextarea <$> areq textareaField (fslpI MsgErrMsgCiphertext "Ciphertext") Nothing)
|
|
<* submitButton
|
|
|
|
plaintext <- formResultMaybe ctResult $ exceptT (\err -> Nothing <$ addMessageI Error err) (return . Just) . (encodedSecretBoxOpen :: Text -> ExceptT EncodedSecretBoxException Handler Value)
|
|
|
|
defaultLayout
|
|
[whamlet|
|
|
$maybe t <- plaintext
|
|
<pre style="white-space:pre-wrap; font-family:monospace">
|
|
#{encodePrettyToTextBuilder t}
|
|
|
|
<form action=@{AdminErrMsgR} method=post enctype=#{ctEncoding}>
|
|
^{ctView}
|
|
|]
|