{-# LANGUAGE ScopedTypeVariables #-}
module Handler.Settings where
import Import
import qualified Network.HTTP.Conduit as HTTP
import Text.XML.Lens
import Data.Bits
import Text.XML (parseText)
import qualified Data.Text.Lazy as T
import qualified Data.ByteString.Lazy.Char8 as B
getSettingsR :: Handler Html
getSettingsR = loginOrDo $ (\(uid,user) -> do
apiKey <- runDB $ getBy $ UniqueApiUser uid
(formWidget, formEnctype) <- generateFormPost $ renderBootstrap3 authFormLayout (authKeyForm (entityVal <$> apiKey) uid)
man <- getHttpManager <$> ask
validKey <- case apiKey of
Just (Entity _ key) -> liftIO $ checkApiKey key man
Nothing -> return False
insertionWidget <- return Nothing :: Handler (Maybe Widget)
loginLayout user $(widgetFile "settings")
)
postSettingsR :: Handler Html
postSettingsR = loginOrDo $ (\(uid,user) -> do
apiKey <- runDB $ getBy $ UniqueApiUser uid
((result,formWidget),formEnctype) <- runFormPost $ renderBootstrap3 authFormLayout (authKeyForm (entityVal <$> apiKey) uid)
(success, msg) <- case result of
FormSuccess api -> do mapi <- runDB $ getBy $ UniqueApiUser uid
case mapi of
Just (Entity aid _) -> runDB $ replace aid api
Nothing -> runDB $ insert_ api
return (True,[whamlet|Successful inserted Key|])
FormFailure errs -> return (False,[whamlet|Error:
#{concat $ intersperse "
" errs}|])
FormMissing -> return (False,[whamlet|Error: No such Form|])
apiKey' <- runDB $ getBy $ UniqueApiUser uid
man <- getHttpManager <$> ask
validKey <- case apiKey' of
Just (Entity _ key) -> liftIO $ checkApiKey key man
Nothing -> return False
insertionWidget <- return . Just $ [whamlet|
$if success