{-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE QuasiQuotes #-} {-# LANGUAGE TupleSections #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE RecordWildCards #-} {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE CPP #-} module Yesod.Form.Functions ( -- * Running in MForm monad newFormIdent , askParams , askFiles -- * Applicative/Monadic conversion , formToAForm , aFormToForm , mFormToWForm , wFormToAForm , wFormToMForm -- * Fields to Forms , wreq , wopt , mreq , mopt , areq , aopt -- * Run a form , runFormPost , runFormPostNoToken , runFormGet -- * Generate a blank form , generateFormPost , generateFormGet' , generateFormGet -- * More than one form on a handler , identifyForm -- * Rendering , FormRender , renderTable , renderDivs , renderDivsNoLabels , renderBootstrap2 -- * Validation , check , checkBool , checkM , checkMMap , customErrorMessage -- * Utilities , fieldSettingsLabel , parseHelper , parseHelperGen , convertField , addClass , removeClass ) where import RIO hiding (ask, local) import Yesod.Form.Types import Yesod.Core.Types (liftHandler) import Data.Text (Text, pack) import qualified Data.Text as T import Control.Arrow (second) import Control.Monad (liftM, join) import Data.Byteable (constEqBytes) import Text.Blaze (Markup, toMarkup) #define Html Markup #define toHtml toMarkup import Yesod.Core import Network.Wai (requestMethod) import Data.Monoid (mempty, (<>)) import Data.Maybe (listToMaybe, fromMaybe) import qualified Data.Map as Map import qualified Data.Text.Encoding as TE import Control.Arrow (first) get :: MForm site Ints get = view (to mfdInts) >>= readIORef put :: Ints -> MForm site () put ints = view (to mfdInts) >>= (`writeIORef` ints) tell :: Enctype -> MForm site () tell ec = view (to mfdEnctype) >>= (`writeIORef` ec) local :: ( Maybe (Env, FileEnv) -> Maybe (Env, FileEnv) ) -> MForm site a -> MForm site a local f inner = do mfd <- view id let mfd' = mfd { mfdParams = f $ mfdParams mfd } runRIO mfd' inner -- | Get a unique identifier. newFormIdent :: MForm site Text newFormIdent = do i <- get let i' = incrInts i put i' return $ pack $ 'f' : show i' where incrInts (IntSingle i) = IntSingle $ i + 1 incrInts (IntCons i is) = (i + 1) `IntCons` is formToAForm :: MForm site (FormResult a, [FieldView site]) -> AForm site a formToAForm mform = AForm $ do WFormData viewsDeque mfd <- view id (a, views) <- runRIO mfd mform for_ views $ pushBackDeque viewsDeque pure a aFormToForm :: AForm site a -> MForm site (FormResult a, [FieldView site] -> [FieldView site]) aFormToForm (AForm wform) = do (res, views) <- wFormToMForm wform pure (res, (views++)) askParams :: MForm site (Maybe Env) askParams = view $ to (fmap fst . mfdParams) askFiles :: MForm site (Maybe FileEnv) askFiles = view $ to (fmap snd . mfdParams) -- | Converts a form field into monadic form 'WForm'. This field requires a -- value and will return 'FormFailure' if left empty. -- -- @since 1.4.14 wreq :: RenderMessage site FormMessage => Field site a -- ^ form field -> FieldSettings site -- ^ settings for this field -> Maybe a -- ^ optional default value -> WForm site (FormResult a) wreq f fs = mFormToWForm . mreq f fs -- | Converts a form field into monadic form 'WForm'. This field is optional, -- i.e. if filled in, it returns 'Just a', if left empty, it returns -- 'Nothing'. Arguments are the same as for 'wreq' (apart from type of default -- value). -- -- @since 1.4.14 wopt :: Field site a -- ^ form field -> FieldSettings site -- ^ settings for this field -> Maybe (Maybe a) -- ^ optional default value -> WForm site (FormResult (Maybe a)) wopt f fs = mFormToWForm . mopt f fs -- | Converts a monadic form 'WForm' into an applicative form 'AForm'. -- -- @since 1.4.14 wFormToAForm :: WForm site (FormResult a) -- ^ input form -> AForm site a -- ^ output form wFormToAForm = formToAForm . wFormToMForm -- | Converts a monadic form 'WForm' into another monadic form 'MForm'. -- -- @since 1.4.14 wFormToMForm :: WForm site a -- ^ input form -> MForm site (a, [FieldView site]) -- ^ output form wFormToMForm wform = do viewsDeque <- newDeque mfd <- view id a <- runRIO (WFormData viewsDeque mfd) wform views <- dequeToList viewsDeque pure (a, views) -- | Converts a monadic form 'MForm' into another monadic form 'WForm'. -- -- @since 1.4.14 mFormToWForm :: MForm site (a, FieldView site) -- ^ input form -> WForm site a -- ^ output form mFormToWForm mform = do WFormData viewsDeque mfd <- view id (a, view') <- runRIO mfd mform pushBackDeque viewsDeque view' pure a -- | Converts a form field into monadic form. This field requires a value -- and will return 'FormFailure' if left empty. mreq :: RenderMessage site FormMessage => Field site a -- ^ form field -> FieldSettings site -- ^ settings for this field -> Maybe a -- ^ optional default value -> MForm site (FormResult a, FieldView site) mreq field fs mdef = mhelper field fs mdef (\m l -> FormFailure [renderMessage m l MsgValueRequired]) FormSuccess True -- | Converts a form field into monadic form. This field is optional, i.e. -- if filled in, it returns 'Just a', if left empty, it returns 'Nothing'. -- Arguments are the same as for 'mreq' (apart from type of default value). mopt :: Field site a -> FieldSettings site -> Maybe (Maybe a) -> MForm site (FormResult (Maybe a), FieldView site) mopt field fs mdef = mhelper field fs (join mdef) (const $ const $ FormSuccess Nothing) (FormSuccess . Just) False mhelper :: Field site a -> FieldSettings site -> Maybe a -> (site -> [Text] -> FormResult b) -- ^ on missing -> (a -> FormResult b) -- ^ on success -> Bool -- ^ is it required? -> MForm site (FormResult b, FieldView site) mhelper Field {..} FieldSettings {..} mdef onMissing onFound isReq = do tell fieldEnctype mp <- askParams name <- maybe newFormIdent return fsName theId <- maybe newIdent return fsId site <- getYesod langs <- reqLangs <$> getRequest let mr2 = renderMessage site langs (res, val) <- case mp of Nothing -> return (FormMissing, maybe (Left "") Right mdef) Just p -> do mfs <- askFiles let mvals = fromMaybe [] $ Map.lookup name p files = fromMaybe [] $ mfs >>= Map.lookup name emx <- liftHandler $ fieldParse mvals files return $ case emx of Left (SomeMessage e) -> (FormFailure [renderMessage site langs e], maybe (Left "") Left (listToMaybe mvals)) Right mx -> case mx of Nothing -> (onMissing site langs, Left "") Just x -> (onFound x, Right x) return (res, FieldView { fvLabel = toHtml $ mr2 fsLabel , fvTooltip = fmap toHtml $ fmap mr2 fsTooltip , fvId = theId , fvInput = fieldView theId name fsAttrs val isReq , fvErrors = case res of FormFailure [e] -> Just $ toHtml e _ -> Nothing , fvRequired = isReq }) -- | Applicative equivalent of 'mreq'. areq :: RenderMessage site FormMessage => Field site a -> FieldSettings site -> Maybe a -> AForm site a areq a b = formToAForm . liftM (second return) . mreq a b -- | Applicative equivalent of 'mopt'. aopt :: Field site a -> FieldSettings site -> Maybe (Maybe a) -> AForm site (Maybe a) aopt a b = formToAForm . liftM (second return) . mopt a b runFormGeneric :: HasHandlerData env => MForm (HandlerSite env) a -> Maybe (Env, FileEnv) -> RIO env (a, Enctype) runFormGeneric mform params = do hd <- liftHandler $ view subHandlerDataL enctypeRef <- newIORef mempty intsRef <- newIORef $! IntSingle 0 let mfd = MFormData { mfdHandlerData = hd , mfdEnctype = enctypeRef , mfdParams = params , mfdInts = intsRef } a <- runRIO mfd mform (,) a <$> readIORef enctypeRef -- | This function is used to both initially render a form and to later extract -- results from it. Note that, due to CSRF protection and a few other issues, -- forms submitted via GET and POST are slightly different. As such, be sure to -- call the relevant function based on how the form will be submitted, /not/ -- the current request method. -- -- For example, a common case is displaying a form on a GET request and having -- the form submit to a POST page. In such a case, both the GET and POST -- handlers should use 'runFormPost'. runFormPost :: (RenderMessage (HandlerSite env) FormMessage, HasHandlerData env) => (Html -> MForm (HandlerSite env) (FormResult a, xml)) -> RIO env ((FormResult a, xml), Enctype) runFormPost form = do env <- postEnv postHelper form env postHelper :: (HasHandlerData env, RenderMessage (HandlerSite env) FormMessage) => (Html -> MForm (HandlerSite env) (FormResult a, xml)) -> Maybe (Env, FileEnv) -> RIO env ((FormResult a, xml), Enctype) postHelper form env = do req <- getRequest let tokenKey = defaultCsrfParamName let token = case reqToken req of Nothing -> Data.Monoid.mempty Just n -> [shamlet||] ((res, xml), enctype) <- runFormGeneric (form token) env site <- getYesod let res' = case (res, env) of (_, Nothing) -> FormMissing (FormSuccess{}, Just (params, _)) | not (Map.lookup tokenKey params === reqToken req) -> FormFailure [renderMessage site (reqLangs req) MsgCsrfWarning] _ -> res -- It's important to use constant-time comparison (constEqBytes) in order to avoid timing attacks. where (Just [t1]) === (Just t2) = TE.encodeUtf8 t1 `constEqBytes` TE.encodeUtf8 t2 Nothing === Nothing = True _ === _ = False return ((res', xml), enctype) -- | Similar to 'runFormPost', except it always ignores the currently available -- environment. This is necessary in cases like a wizard UI, where a single -- page will both receive and incoming form and produce a new, blank form. For -- general usage, you can stick with @runFormPost@. generateFormPost :: (RenderMessage (HandlerSite env) FormMessage, HasHandlerData env) => (Html -> MForm (HandlerSite env) (FormResult a, xml)) -> RIO env (xml, Enctype) generateFormPost form = first snd `liftM` postHelper form Nothing postEnv :: HasHandlerData env => RIO env (Maybe (Env, FileEnv)) postEnv = do req <- getRequest if requestMethod (reqWaiRequest req) == "GET" then return Nothing else do (p, f) <- runRequestBody let p' = Map.unionsWith (++) $ map (\(x, y) -> Map.singleton x [y]) p return $ Just (p', Map.unionsWith (++) $ map (\(k, v) -> Map.singleton k [v]) f) runFormPostNoToken :: HasHandlerData env => (Html -> MForm (HandlerSite env) a) -> RIO env (a, Enctype) runFormPostNoToken form = do params <- postEnv runFormGeneric (form mempty) params runFormGet :: HasHandlerData env => (Html -> MForm (HandlerSite env) a) -> RIO env (a, Enctype) runFormGet form = do gets <- liftM reqGetParams getRequest let env = case lookup getKey gets of Nothing -> Nothing Just _ -> Just (Map.unionsWith (++) $ map (\(x, y) -> Map.singleton x [y]) gets, Map.empty) getHelper form env {- FIXME: generateFormGet' "Will be renamed to generateFormGet in next version of Yesod" -} -- | -- -- Since 1.3.11 generateFormGet' :: HasHandlerData env => (Html -> MForm (HandlerSite env) (FormResult a, xml)) -> RIO env (xml, Enctype) generateFormGet' form = first snd `liftM` getHelper form Nothing {-# DEPRECATED generateFormGet "Will require RenderMessage in next version of Yesod" #-} generateFormGet :: HasHandlerData env => (Html -> MForm (HandlerSite env) a) -> RIO env (a, Enctype) generateFormGet form = getHelper form Nothing getKey :: Text getKey = "_hasdata" getHelper :: HasHandlerData env => (Html -> MForm (HandlerSite env) a) -> Maybe (Env, FileEnv) -> RIO env (a, Enctype) getHelper form params = do let fragment = [shamlet||] runFormGeneric (form fragment) params -- | Creates a hidden field on the form that identifies it. This -- identification is then used to distinguish between /missing/ -- and /wrong/ form data when a single handler contains more than -- one form. -- -- For instance, if you have the following code on your handler: -- -- > ((fooRes, fooWidget), fooEnctype) <- runFormPost fooForm -- > ((barRes, barWidget), barEnctype) <- runFormPost barForm -- -- Then replace it with -- -- > ((fooRes, fooWidget), fooEnctype) <- runFormPost $ identifyForm "foo" fooForm -- > ((barRes, barWidget), barEnctype) <- runFormPost $ identifyForm "bar" barForm -- -- Note that it's your responsibility to ensure that the -- identification strings are unique (using the same one twice on a -- single handler will not generate any errors). This allows you -- to create a variable number of forms and still have them work -- even if their number or order change between the HTML -- generation and the form submission. identifyForm :: Text -- ^ Form identification string. -> (Html -> MForm site (FormResult a, WidgetFor site ())) -> (Html -> MForm site (FormResult a, WidgetFor site ())) identifyForm identVal form = \fragment -> do -- Create hidden . let fragment' = [shamlet| #{fragment} |] -- Check if we got its value back. mp <- askParams let missing = (mp >>= Map.lookup identifyFormKey) /= Just ["identify-" <> identVal] -- Run the form proper (with our hidden ). If the -- data is missing, then do not provide any params to the -- form, which will turn its result into FormMissing. Also, -- doing this avoids having lots of fields with red errors. let eraseParams | missing = local (const Nothing) | otherwise = id ( res', w) <- eraseParams (form fragment') -- Empty forms now properly return FormMissing. [#1072](https://github.com/yesodweb/yesod/issues/1072) let res = if missing then FormMissing else res' return ( res, w) identifyFormKey :: Text identifyFormKey = "_formid" type FormRender site a = AForm site a -> Html -> MForm site (FormResult a, WidgetFor site ()) renderTable, renderDivs, renderDivsNoLabels :: FormRender env a -- | Render a form into a series of tr tags. Note that, in order to allow -- you to add extra rows to the table, this function does /not/ wrap up -- the resulting HTML in a table tag; you must do that yourself. renderTable aform fragment = do (res, views') <- aFormToForm aform let views = views' [] let widget = [whamlet| $newline never $if null views \#{fragment} $forall (isFirst, view) <- addIsFirst views