Safe Haskell | Safe-Inferred |
---|---|
Language | GHC2021 |
Synopsis
- newtype FormFields f id = FormFields id
- data FieldInput
- data Label a
- data Input a = Input
- newtype InputName = InputName Text
- field :: Mod -> View (Input id) () -> View (FormFields form id) ()
- label :: Text -> View (Input id) ()
- input :: FieldInput -> Mod -> InputName -> View (Input id) ()
- form :: forall form id. (Form form, HyperView id) => Action id -> Mod -> (form Label -> View (FormFields form id) ()) -> View id ()
- submit :: Mod -> View (FormFields form id) () -> View (FormFields form id) ()
- parseForm :: forall form es. (Form form, Hyperbole :> es) => Eff es (form Identity)
- class Form (form :: (Type -> Type) -> Type) where
- type family Field (context :: Type -> Type) a
- class GFormLabels f where
- gFormLabels :: f p
Documentation
newtype FormFields f id Source #
The only time we can use Fields is inside a form
FormFields id |
Instances
Show id => Show (FormFields f id) Source # | |
Defined in Web.Hyperbole.Forms showsPrec :: Int -> FormFields f id -> ShowS # show :: FormFields f id -> String # showList :: [FormFields f id] -> ShowS # | |
(HyperView id, Show id) => HyperView (FormFields f id) Source # | |
Defined in Web.Hyperbole.Forms type Action (FormFields f id) Source # | |
(Param id, Show id) => Param (FormFields f id) Source # | |
Defined in Web.Hyperbole.Forms parseParam :: Text -> Maybe (FormFields f id) Source # toParam :: FormFields f id -> Text Source # | |
type Action (FormFields f id) Source # | |
Defined in Web.Hyperbole.Forms |
data FieldInput Source #
TODO: there are many more of these: https://developer.mozilla.org/en-US/docs/Web/HTML/Attributes/autocomplete
NewPassword | |
CurrentPassword | |
Username | |
Number | |
TextInput | |
Name | |
OneTimeCode | |
Organization | |
StreetAddress | |
Country | |
CountryName | |
PostalCode | |
Search |
Instances
Show FieldInput Source # | |
Defined in Web.Hyperbole.Forms showsPrec :: Int -> FieldInput -> ShowS # show :: FieldInput -> String # showList :: [FieldInput] -> ShowS # |
form :: forall form id. (Form form, HyperView id) => Action id -> Mod -> (form Label -> View (FormFields form id) ()) -> View id () Source #
submit :: Mod -> View (FormFields form id) () -> View (FormFields form id) () Source #
class Form (form :: (Type -> Type) -> Type) where Source #
Nothing
formLabels :: form Label Source #
default formLabels :: (Generic (form Label), GFormLabels (Rep (form Label))) => form Label Source #
class GFormLabels f where Source #
Automatically derive labels from form field names
gFormLabels :: f p Source #
Instances
GFormLabels (U1 :: k -> Type) Source # | |
Defined in Web.Hyperbole.Forms gFormLabels :: forall (p :: k0). U1 p Source # | |
(GFormLabels f, GFormLabels g) => GFormLabels (f :*: g :: k -> Type) Source # | |
Defined in Web.Hyperbole.Forms gFormLabels :: forall (p :: k0). (f :*: g) p Source # | |
GFormLabels f => GFormLabels (M1 C c f :: k -> Type) Source # | |
Defined in Web.Hyperbole.Forms gFormLabels :: forall (p :: k0). M1 C c f p Source # | |
GFormLabels f => GFormLabels (M1 D d f :: k -> Type) Source # | |
Defined in Web.Hyperbole.Forms gFormLabels :: forall (p :: k0). M1 D d f p Source # | |
Selector s => GFormLabels (M1 S s (K1 R InputName :: k -> Type) :: k -> Type) Source # | |
Defined in Web.Hyperbole.Forms |