hyperbole-0.2.0: Web Framework inspired by HTMX
Safe HaskellSafe-Inferred
LanguageGHC2021

Web.Hyperbole.Forms

Synopsis

Documentation

newtype FormFields f id Source #

The only time we can use Fields is inside a form

Constructors

FormFields id 

Instances

Instances details
Show id => Show (FormFields f id) Source # 
Instance details

Defined in Web.Hyperbole.Forms

Methods

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 # 
Instance details

Defined in Web.Hyperbole.Forms

Associated Types

type Action (FormFields f id) Source #

(Param id, Show id) => Param (FormFields f id) Source # 
Instance details

Defined in Web.Hyperbole.Forms

type Action (FormFields f id) Source # 
Instance details

Defined in Web.Hyperbole.Forms

type Action (FormFields f id) = Action id

data Label a Source #

Instances

Instances details
type Field (Label :: Type -> Type) a Source # 
Instance details

Defined in Web.Hyperbole.Forms

type Field (Label :: Type -> Type) a = InputName

data Input a Source #

Constructors

Input 

newtype InputName Source #

Constructors

InputName Text 

Instances

Instances details
Selector s => GFormLabels (M1 S s (K1 R InputName :: k -> Type) :: k -> Type) Source # 
Instance details

Defined in Web.Hyperbole.Forms

Methods

gFormLabels :: forall (p :: k0). M1 S s (K1 R InputName) p Source #

field :: Mod -> View (Input id) () -> View (FormFields form id) () Source #

label :: Text -> View (Input id) () Source #

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 #

parseForm :: forall form es. (Form form, Hyperbole :> es) => Eff es (form Identity) Source #

class Form (form :: (Type -> Type) -> Type) where Source #

Minimal complete definition

Nothing

Methods

formLabels :: form Label Source #

default formLabels :: (Generic (form Label), GFormLabels (Rep (form Label))) => form Label Source #

fromForm :: Form -> Either Text (form Identity) Source #

default fromForm :: (Generic (form Identity), GFromForm (form Identity) (Rep (form Identity))) => Form -> Either Text (form Identity) Source #

type family Field (context :: Type -> Type) a Source #

Instances

Instances details
type Field Identity a Source # 
Instance details

Defined in Web.Hyperbole.Forms

type Field Identity a = a
type Field (Label :: Type -> Type) a Source # 
Instance details

Defined in Web.Hyperbole.Forms

type Field (Label :: Type -> Type) a = InputName

class GFormLabels f where Source #

Automatically derive labels from form field names

Methods

gFormLabels :: f p Source #

Instances

Instances details
GFormLabels (U1 :: k -> Type) Source # 
Instance details

Defined in Web.Hyperbole.Forms

Methods

gFormLabels :: forall (p :: k0). U1 p Source #

(GFormLabels f, GFormLabels g) => GFormLabels (f :*: g :: k -> Type) Source # 
Instance details

Defined in Web.Hyperbole.Forms

Methods

gFormLabels :: forall (p :: k0). (f :*: g) p Source #

GFormLabels f => GFormLabels (M1 C c f :: k -> Type) Source # 
Instance details

Defined in Web.Hyperbole.Forms

Methods

gFormLabels :: forall (p :: k0). M1 C c f p Source #

GFormLabels f => GFormLabels (M1 D d f :: k -> Type) Source # 
Instance details

Defined in Web.Hyperbole.Forms

Methods

gFormLabels :: forall (p :: k0). M1 D d f p Source #

Selector s => GFormLabels (M1 S s (K1 R InputName :: k -> Type) :: k -> Type) Source # 
Instance details

Defined in Web.Hyperbole.Forms

Methods

gFormLabels :: forall (p :: k0). M1 S s (K1 R InputName) p Source #