{-# LANGUAGE QuasiQuotes #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE GeneralizedNewtypeDeriving #-} {-# LANGUAGE CPP #-} module Yesod.Form.Profiles ( stringFieldProfile , passwordFieldProfile , textareaFieldProfile , hiddenFieldProfile , intFieldProfile , dayFieldProfile , timeFieldProfile , htmlFieldProfile , emailFieldProfile , searchFieldProfile , AutoFocus , urlFieldProfile , doubleFieldProfile , parseDate , parseTime , Textarea (..) ) where import Yesod.Form.Core import Yesod.Widget import Text.Hamlet hiding (renderHtml) import Text.Blaze (ToHtml (..)) import Text.Cassius import Data.Time (Day, TimeOfDay(..)) import qualified Text.Email.Validate as Email import Network.URI (parseURI) import Database.Persist (PersistField) import Text.HTML.SanitizeXSS (sanitizeBalance) import Control.Monad (when) import qualified Blaze.ByteString.Builder.Html.Utf8 as B import Blaze.ByteString.Builder (writeByteString, toLazyByteString) import Blaze.ByteString.Builder.Internal.Write (fromWriteList) import Text.Blaze.Renderer.String (renderHtml) import qualified Data.ByteString as S import qualified Data.ByteString.Lazy as L import Data.Text (Text, unpack, pack) #if __GLASGOW_HASKELL__ >= 700 #define HAMLET hamlet #define CASSIUS cassius #define JULIUS julius #else #define HAMLET $hamlet #define CASSIUS $cassius #define JULIUS $julius #endif intFieldProfile :: Integral i => FieldProfile sub y i intFieldProfile = FieldProfile { fpParse = maybe (Left "Invalid integer") Right . readMayI . unpack -- FIXME Data.Text.Read , fpRender = pack . showI , fpWidget = \theId name val isReq -> addHamlet [HAMLET|\ |] } where showI x = show (fromIntegral x :: Integer) readMayI s = case reads s of (x, _):_ -> Just $ fromInteger x [] -> Nothing doubleFieldProfile :: FieldProfile sub y Double doubleFieldProfile = FieldProfile { fpParse = maybe (Left "Invalid number") Right . readMay . unpack -- FIXME use Data.Text.Read , fpRender = pack . show , fpWidget = \theId name val isReq -> addHamlet [HAMLET|\ |] } dayFieldProfile :: FieldProfile sub y Day dayFieldProfile = FieldProfile { fpParse = parseDate . unpack , fpRender = pack . show , fpWidget = \theId name val isReq -> addHamlet [HAMLET|\ |] } timeFieldProfile :: FieldProfile sub y TimeOfDay timeFieldProfile = FieldProfile { fpParse = parseTime . unpack , fpRender = pack . show . roundFullSeconds , fpWidget = \theId name val isReq -> addHamlet [HAMLET|\ |] } where roundFullSeconds tod = TimeOfDay (todHour tod) (todMin tod) fullSec where fullSec = fromInteger $ floor $ todSec tod htmlFieldProfile :: FieldProfile sub y Html htmlFieldProfile = FieldProfile { fpParse = Right . preEscapedString . sanitizeBalance . unpack -- FIXME make changes to xss-sanitize , fpRender = pack . renderHtml , fpWidget = \theId name val _isReq -> addHamlet [HAMLET|\