{-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE AllowAmbiguousTypes #-} {-# LANGUAGE InstanceSigs, UndecidableInstances, AllowAmbiguousTypes, ScopedTypeVariables, IncoherentInstances #-} {-| Module: IHP.View.Form Description: 'IHP.View.Form.formFor' and all form controls Copyright: (c) digitally induced GmbH, 2020 -} module IHP.View.Form where import IHP.Prelude import IHP.ValidationSupport import IHP.HSX.ConvertibleStrings () import IHP.ViewErrorMessages () import IHP.ViewSupport import qualified Text.Blaze.Html5 as Html5 import IHP.HSX.ToHtml import GHC.Types import IHP.ModelSupport (getModelName, inputValue, isNew, Id', InputValue, didTouchField) import IHP.HSX.QQ (hsx) import IHP.View.Types import IHP.View.Classes () import Network.Wai (pathInfo) import IHP.Controller.Context -- | Forms usually begin with a 'formFor' expression. -- -- This is how a simple form can look like: -- -- > renderForm :: Post -> Html -- > renderForm post = formFor post [hsx| -- > {textField #title} -- > {textareaField #body} -- > {submitButton} -- > |] -- -- Calling this form from inside your HSX code will lead to the following HTML being generated: -- -- >
-- >
-- > -- > -- >
-- > -- >
-- > -- > -- >
-- > -- > -- >
-- -- You can see that the form is submitted via @POST@. The form action has also been set by default to @/CreatePost@. -- -- All inputs have auto-generated class names and ids for styling. Also, all @name@ attributes are set as expected. -- -- __Field Values:__ -- -- A form control is always filled with the value of the given field when rendering. For example, given a post -- -- > let post = Post { ..., title = "Hello World" } -- -- Rendering this, the input value will be set like: -- -- >>> {textField #title} -- -- -- __Validation:__ -- -- When rendering a record that has failed validation, the validation error message will be rendered automatically. -- -- Given a post like this: -- -- > let post = Post { ..., title = "" } -- > |> validateField #title nonEmpty -- -- Rendering @{textField #title}@, the input will have the css class @is-invalid@ and an element with the error message will be rendered below the input: -- -- >
-- > -- > type="text" -- > name="title" -- > placeholder="" -- > id="post_title" -- > class="form-control is-invalid " -- > /> -- >
This field cannot be empty
-- >
formFor :: forall record. ( ?context :: ControllerContext , ModelFormAction record , HasField "meta" record MetaBag ) => record -> ((?context :: ControllerContext, ?formContext :: FormContext record) => Html5.Html) -> Html5.Html formFor record formBody = formForWithOptions @record record (\c -> c) formBody {-# INLINE formFor #-} -- | Like 'formFor' but allows changing the underlying 'FormContext' -- -- This is how you can render a form with a @id="post-form"@ id attribute and a custom @data-post-id@ attribute: -- -- > renderForm :: Post -> Html -- > renderForm post = formForWithOptions formOptions post [hsx| -- > {textField #title} -- > {textareaField #body} -- > {submitButton} -- > |] -- > -- > formOptions :: FormContext Post -> FormContext Post -- > formOptions formContext = formContext -- > |> set #formId "post-form" -- > |> set #customFormAttributes [("data-post-id", show formContext.model.id)] -- formForWithOptions :: forall record. ( ?context :: ControllerContext , ModelFormAction record , HasField "meta" record MetaBag ) => record -> (FormContext record -> FormContext record) -> ((?context :: ControllerContext, ?formContext :: FormContext record) => Html5.Html) -> Html5.Html formForWithOptions record applyOptions formBody = buildForm (applyOptions (createFormContext record) { formAction = modelFormAction record }) formBody {-# INLINE formForWithOptions #-} -- | Like 'formFor' but disables the IHP javascript helpers. -- -- Use it like this: -- -- > renderForm :: Post -> Html -- > renderForm post = formForWithoutJavascript post [hsx| -- > {textField #title} -- > {textareaField #body} -- > {submitButton} -- > |] -- -- If you want to use this with e.g. a custom form action, remember that 'formForWithoutJavascript' is just a shortcut for 'formForWithOptions': -- -- > renderForm :: Post -> Html -- > renderForm post = formForWithOptions formOptions post [hsx| -- > {textField #title} -- > {textareaField #body} -- > {submitButton} -- > |] -- > -- > formOptions :: FormContext Post -> FormContext Post -- > formOptions formContext = formContext -- > |> set #formAction (pathTo BespokeNewPostAction) -- > |> set #disableJavascriptSubmission True -- formForWithoutJavascript :: forall record. ( ?context :: ControllerContext , ModelFormAction record , HasField "meta" record MetaBag ) => record -> ((?context :: ControllerContext, ?formContext :: FormContext record) => Html5.Html) -> Html5.Html formForWithoutJavascript record formBody = formForWithOptions @record record (\formContext -> formContext { disableJavascriptSubmission = True }) formBody {-# INLINE formForWithoutJavascript #-} -- | Allows a custom form action (form submission url) to be set -- -- The URL where the form is going to be submitted to is specified in HTML using the form's @action@ attribute. When using 'formFor' the @action@ attribute is automatically set to the expected path. -- -- E.g. given the below 'formFor' code, the @action@ is set to @/CreatePost@ or @/UpdatePost@: -- -- > renderForm :: Post -> Html -- > renderForm post = formFor post [hsx| -- > {textField #title} -- > {textareaField #body} -- > {submitButton} -- > |] -- -- To override the auto-generated @action@ attribute use the 'formFor\'' function: -- -- > renderForm :: Post -> Html -- > renderForm post = formFor' post "/my-custom-endpoint" [hsx||] -- -- If you pass an action to that, you need to wrap it with 'pathTo': -- -- > renderForm :: Post -> Html -- > renderForm post = formFor' post (pathTo CreateDraftAction) [hsx||] -- formFor' :: forall record. ( ?context :: ControllerContext , HasField "meta" record MetaBag ) => record -> Text -> ((?context :: ControllerContext, ?formContext :: FormContext record) => Html5.Html) -> Html5.Html formFor' record action = buildForm (createFormContext record) { formAction = action } {-# INLINE formFor' #-} -- | Used by 'formFor' to make a new form context createFormContext :: forall record. ( ?context :: ControllerContext , HasField "meta" record MetaBag ) => record -> FormContext record createFormContext record = FormContext { model = record , formAction = "" , formMethod = "POST" , cssFramework = theCSSFramework , formId = "" , formClass = if isNew record then "new-form" else "edit-form" , customFormAttributes = [] , disableJavascriptSubmission = False , fieldNamePrefix = "" } {-# INLINE createFormContext #-} -- | Used by 'formFor' to render the form buildForm :: forall model. (?context :: ControllerContext) => FormContext model -> ((?context :: ControllerContext, ?formContext :: FormContext model) => Html5.Html) -> Html5.Html buildForm formContext inner = [hsx|
{formInner}
|] where formInner = let ?formContext = formContext in inner {-# INLINE buildForm #-} nestedFormFor :: forall fieldName childRecord parentRecord idType. ( ?context :: ControllerContext , ?formContext :: FormContext parentRecord , HasField fieldName parentRecord [childRecord] , KnownSymbol fieldName , KnownSymbol (GetModelName childRecord) , HasField "id" childRecord idType , InputValue idType , HasField "meta" childRecord MetaBag ) => Proxy fieldName -> ((?context :: ControllerContext, ?formContext :: FormContext childRecord) => Html5.Html) -> Html5.Html nestedFormFor field nestedRenderForm = forEach children renderChild where parentFormContext :: FormContext parentRecord parentFormContext = ?formContext renderChild :: childRecord -> Html5.Html renderChild record = let ?formContext = buildNestedFormContext record in [hsx| {hiddenField #id} {nestedRenderForm} |] buildNestedFormContext :: childRecord -> FormContext childRecord buildNestedFormContext record = parentFormContext { model = record, fieldNamePrefix = symbolToText @fieldName <> "_" } children :: [childRecord] children = getField @fieldName ?formContext.model {-# INLINE nestedFormFor #-} -- | Renders a submit button -- -- > -- -- __Example:__ -- -- > renderForm :: Post -> Html -- > renderForm post = formFor post [hsx| -- > {submitButton} -- > |] -- -- This will generate code like this: -- -- >
-- > -- >
-- -- __Custom Text__ -- -- > renderForm :: Post -> Html -- > renderForm post = formFor post [hsx| -- > {submitButton { label = "Create it!" } } -- > |] -- -- This will generate code like this: -- -- >
-- > -- >
-- -- __Custom Class__ -- -- > renderForm :: Post -> Html -- > renderForm post = formFor post [hsx| -- > {submitButton { buttonClass = "create-button" } } -- > |] -- -- This will generate code like this: -- -- >
-- > -- >
-- -- __Disabled button__ -- -- > renderForm :: Post -> Html -- > renderForm post = formFor post [hsx| -- > {submitButton { buttonDisabled = True } } -- > |] -- -- This will generate code like this: -- -- >
-- > -- >
submitButton :: forall model. (?formContext :: FormContext model, HasField "meta" model MetaBag, KnownSymbol (GetModelName model)) => SubmitButton submitButton = let modelName = IHP.ModelSupport.getModelName @model buttonText = modelName |> humanize -- We do this to turn 'Create ProjectTask' into 'Create Project Task' isNew = IHP.ModelSupport.isNew (model ?formContext) in SubmitButton { label = cs $ (if isNew then "Create " else "Save ") <> buttonText , buttonClass = mempty , buttonDisabled = False , cssFramework = ?formContext.cssFramework } {-# INLINE submitButton #-} -- | Renders a text input field -- -- >>> {textField #title} --
-- -- --
-- -- __Example:__ -- -- > renderForm :: Post -> Html -- > renderForm post = formFor post [hsx| -- > {textField #title} -- > |] -- -- This will generate code like this: -- -- >
-- >
-- > -- > -- >
-- >
-- -- __Help Texts:__ -- -- You can add a help text below a form control like this: -- -- > {(textField #title) { helpText = "Max. 140 characters"} } -- -- This will generate code like this: -- -- >
-- > -- > -- > -- > Max. 140 characters -- >
-- -- -- __Custom Field Label Text:__ -- -- By default, the field name will be used as a label text. The camel case field name will be made more human-readable of course, so @contactName@ will turn to @Contact Name@, etc. Sometimes you want to change this auto-generated input label to something custom. Use @fieldLabel@ for that, like this: -- -- > {(textField #title) { fieldLabel = "Post Title"} } -- -- This will generate code like this: -- -- >
-- > -- > -- >
-- -- -- __Custom CSS Classes:__ -- -- You can add custom CSS classes to the input and label for better styling. Set @fieldClass@ for adding a class to the input element and @labelClass@ for the label element: -- -- > {(textField #title) { fieldClass="title-input", labelClass = "title-label" } } -- -- This will generate code like this: -- -- >
-- > -- > type="text" -- > name="title" -- > id="post_title" -- > class="form-control title-input" -- > /> -- >
-- -- Of course, the CSS classes for validation are still set as expected. -- -- __Placeholder:__ -- -- > {(textField #title) { placeholder = "Enter your title ..." } } -- -- This will generate code like this: -- -- >
-- > -- > -- > type="text" -- > name="title" -- > id="post_title" -- > placeholder="Enter your title ..." -- > class="form-control" -- > /> -- >
-- -- -- __Required Fields:__ -- -- You can mark an input as required like this: -- -- > {(textField #title) { required = True } } -- -- This will generate code like this: -- -- >
-- > -- > -- > type="text" -- > name="title" -- > id="post_title" -- > required="required" -- > class="form-control" -- > /> -- >
-- -- __Autofocus:__ -- -- You can mark an input with autofocus, to ensure it will be given the input focus on page load, like this: -- -- > {(textField #title) { autofocus = True } } -- -- This will generate code like this: -- -- >
-- > -- > -- > type="text" -- > name="title" -- > id="post_title" -- > autofocus="autofocus" -- > class="form-control" -- > /> -- >
textField :: forall fieldName model value. ( ?formContext :: FormContext model , HasField fieldName model value , HasField "meta" model MetaBag , KnownSymbol fieldName , InputValue value , KnownSymbol (GetModelName model) ) => Proxy fieldName -> FormField textField field = FormField { fieldType = TextInput , fieldName = ?formContext.fieldNamePrefix <> cs fieldName , fieldLabel = fieldNameToFieldLabel (cs fieldName) , fieldValue = inputValue ((getField @fieldName model) :: value) , fieldInputId = cs (lcfirst (getModelName @model) <> "_" <> cs fieldName) , validatorResult = getValidationViolation field model , fieldClass = "" , labelClass = "" , disabled = False , disableLabel = False , disableGroup = False , disableValidationResult = False , additionalAttributes = [] , cssFramework = ?formContext.cssFramework , helpText = "" , placeholder = "" , required = False , autofocus = False } where fieldName = symbolVal field FormContext { model } = ?formContext {-# INLINE textField #-} -- | Renders a number input field -- -- >>> {numberField #maxUsers} --
-- -- --
-- -- See 'textField' for examples of possible form control options. numberField :: forall fieldName model value. ( ?formContext :: FormContext model , HasField fieldName model value , HasField "meta" model MetaBag , KnownSymbol fieldName , InputValue value , KnownSymbol (GetModelName model) ) => Proxy fieldName -> FormField numberField field = (textField field) { fieldType = NumberInput } {-# INLINE numberField #-} -- | Renders a URL input field -- -- >>> {urlField #url} --
-- -- --
-- -- See 'textField' for examples of possible form control options. urlField :: forall fieldName model value. ( ?formContext :: FormContext model , HasField fieldName model value , HasField "meta" model MetaBag , KnownSymbol fieldName , InputValue value , KnownSymbol (GetModelName model) ) => Proxy fieldName -> FormField urlField field = (textField field) { fieldType = UrlInput } {-# INLINE urlField #-} -- | Renders a textarea -- -- >>> {textareaField #body} --
-- --