{-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE AllowAmbiguousTypes #-} {-# LANGUAGE InstanceSigs, UndecidableInstances, AllowAmbiguousTypes, ScopedTypeVariables, IncoherentInstances #-} module IHP.View.Types ( FormField (..) , SubmitButton (..) , FormContext (..) , InputType (..) , CSSFramework (..) , BreadcrumbsView(..) , PaginationView(..) , HtmlWithContext , Layout ) where import IHP.Prelude hiding (div) import qualified Text.Blaze.Html5 as Blaze import IHP.FlashMessages.Types import IHP.ModelSupport (Violation) import IHP.Breadcrumb.Types import IHP.Pagination.Types type HtmlWithContext context = (?context :: context) => Blaze.Html -- | A layout is just a function taking a view and returning a new view. -- -- __Example:__ A very basic html layout. -- -- > myLayout :: Layout -- > myLayout view = [hsx| -- > -- >
-- > {view} -- > -- > -- > |] type Layout = Blaze.Html -> Blaze.Html data FormField = FormField { fieldType :: !InputType , fieldName :: !Text , fieldLabel :: !Text , fieldValue :: !Text , fieldInputId :: !Text , validatorResult :: !(Maybe Violation) , additionalAttributes :: [(Text, Text)] , fieldClass :: !Text , labelClass :: !Text , disabled :: !Bool , disableLabel :: !Bool , disableGroup :: !Bool , disableValidationResult :: !Bool , cssFramework :: CSSFramework , helpText :: !Text , placeholder :: !Text , required :: Bool , autofocus :: Bool } data SubmitButton = SubmitButton { label :: Blaze.Html , buttonClass :: Text , buttonDisabled :: Bool , cssFramework :: CSSFramework } data FormContext model = FormContext { model :: model -- ^ The record this form is based on , formAction :: !Text -- ^ Url where the form is submitted to , formMethod :: !Text -- ^ Usually "POST", sometimes set to "GET" , cssFramework :: !CSSFramework , formClass :: !Text -- ^ In the generated HTML, the @class@ attribute will be set to this value , formId :: !Text -- ^ In the generated HTML, the @id@ attribute will be set to this value , disableJavascriptSubmission :: !Bool -- ^ When set to True, the IHP helpers.js will not submit the form using ajax , customFormAttributes :: ![(Text, Text)] -- ^ Attach custom HTML attributes here , fieldNamePrefix :: !Text -- ^ Used by nested forms to preprend the nested field name to the field name } instance SetField "model" (FormContext record) record where setField value record = record { model = value } instance SetField "formAction" (FormContext record) Text where setField value record = record { formAction = value } instance SetField "formMethod" (FormContext record) Text where setField value record = record { formMethod = value } instance SetField "cssFramework" (FormContext record) CSSFramework where setField value record = record { cssFramework = value } instance SetField "formClass" (FormContext record) Text where setField value record = record { formClass = value } instance SetField "formId" (FormContext record) Text where setField value record = record { formId = value } instance SetField "disableJavascriptSubmission" (FormContext record) Bool where setField value record = record { disableJavascriptSubmission = value } instance SetField "customFormAttributes" (FormContext record) [(Text, Text)] where setField value record = record { customFormAttributes = value } data InputType = TextInput | NumberInput | UrlInput | CheckboxInput | ColorInput | EmailInput | HiddenInput | TextareaInput | DateInput | DateTimeInput | PasswordInput | SelectInput { options :: ![(Text, Text)] } | RadioInput { options :: ![(Text, Text)] } | FileInput data BreadcrumbsView = BreadcrumbsView { breadcrumbItems :: !Blaze.Html } data PaginationView = PaginationView { cssFramework :: !CSSFramework , pagination :: !Pagination -- Function used to get the page URL. , pageUrl :: Int -> ByteString -- Previous page link. , linkPrevious :: !Blaze.Html -- Next page link. , linkNext :: !Blaze.Html -- The page and dot dot as rendered by `styledPaginationPageLink` and `styledPaginationDotDot`. , pageDotDotItems :: !Blaze.Html -- Selector changing the number of allowed items per page. , itemsPerPageSelector :: !Blaze.Html } -- | Render functions to render with Bootstrap, Tailwind CSS etc. -- We call this functions with the cssFramework passed to have late binding (like from OOP languages). -- Here's an explanation breaking it down, step by step -- -- > renderedHtml = styledPagination theCSSFramework theCSSFramework paginationView -- -- Can also be written using get: -- -- > renderedHtml = (theCSSFramework.styledPagination) theCSSFramework paginationView -- -- That's important to understand here. We get a 'styledPagination' function using 'theCSSFramework.styledPagination'. -- Next, we apply 'theCSSFramework' to that function. We do that so because the 'styledPagination' function internally -- might want to call other functions of the CSSFramework type. But we might want to override some functions of the CSSFramework. -- -- Here's an example of how it would look if we don't pass this a second time, and it's shortcomings. -- Let's assume 'styledPagination' is calling a 'styledButton': -- -- > data CSSFramework = CSSFramework { styledPagination :: Html, styledButton :: Html } -- > -- > bootstrapCSS = CSSFramework { styledPagination, styledButton } -- > where -- > styledPagination = [hsx|