{-# LANGUAGE RecordWildCards, OverloadedStrings #-}
{-# OPTIONS_GHC -F -pgmFhsx2hs #-}
module Clckwrks.ProfileData.EditProfileData where
import Clckwrks
import Clckwrks.Admin.Template (template)
import Clckwrks.ProfileData.Acid (GetProfileData(..), SetProfileData(..), profileDataErrorStr)
import Data.Text (pack)
import qualified Data.Text as Text
import Data.Text.Lazy (Text)
import Data.Maybe (fromMaybe)
import Data.UserId (UserId)
import Text.Reform ((++>), mapView, transformEitherM)
import Text.Reform.HSP.Text (form, inputText, inputSubmit, labelText, fieldset, ol, li, errorList, setAttrs)
import Text.Reform.Happstack (reform)
import HSP.XMLGenerator
import HSP.XML
-- FIXME: this currently uses the admin template. Which is sort of right, and sort of not.
editProfileDataPage :: ProfileDataURL -> Clck ProfileDataURL Response
editProfileDataPage here =
do mUid <- getUserId
case mUid of
Nothing -> internalServerError $ toResponse $ ("Unable to retrieve your userid" :: Text)
(Just uid) ->
do pd <- query (GetProfileData uid)
action <- showURL here
template "Edit Profile Data" () $
<%>
<% reform (form action) "epd" updated Nothing (profileDataFormlet pd) %>