web-rep-0.10.0: representations of a web page
Safe HaskellSafe-Inferred
LanguageHaskell2010

Web.Rep.Html.Input

Description

Common web page input elements, often with bootstrap scaffolding.

Synopsis

Documentation

data Input a Source #

something that might exist on a web page and be a front-end input to computations.

Constructors

Input 

Fields

Instances

Instances details
Generic (Input a) Source # 
Instance details

Defined in Web.Rep.Html.Input

Associated Types

type Rep (Input a) :: Type -> Type #

Methods

from :: Input a -> Rep (Input a) x #

to :: Rep (Input a) x -> Input a #

Show a => Show (Input a) Source # 
Instance details

Defined in Web.Rep.Html.Input

Methods

showsPrec :: Int -> Input a -> ShowS #

show :: Input a -> String #

showList :: [Input a] -> ShowS #

Eq a => Eq (Input a) Source # 
Instance details

Defined in Web.Rep.Html.Input

Methods

(==) :: Input a -> Input a -> Bool #

(/=) :: Input a -> Input a -> Bool #

ToHtml a => ToHtml (Input a) Source # 
Instance details

Defined in Web.Rep.Html.Input

Methods

toHtml :: forall (m :: Type -> Type). Monad m => Input a -> HtmlT m () #

toHtmlRaw :: forall (m :: Type -> Type). Monad m => Input a -> HtmlT m () #

type Rep (Input a) Source # 
Instance details

Defined in Web.Rep.Html.Input

type Rep (Input a) = D1 ('MetaData "Input" "Web.Rep.Html.Input" "web-rep-0.10.0-14Ea0acHNZAIpwuRPiHk6A" 'False) (C1 ('MetaCons "Input" 'PrefixI 'True) ((S1 ('MetaSel ('Just "inputVal") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 a) :*: S1 ('MetaSel ('Just "inputLabel") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe Text))) :*: (S1 ('MetaSel ('Just "inputId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Text) :*: S1 ('MetaSel ('Just "inputType") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 InputType))))

data InputType Source #

Various types of web page inputs, encapsulating practical bootstrap class functionality

Instances

Instances details
Generic InputType Source # 
Instance details

Defined in Web.Rep.Html.Input

Associated Types

type Rep InputType :: Type -> Type #

Show InputType Source # 
Instance details

Defined in Web.Rep.Html.Input

Eq InputType Source # 
Instance details

Defined in Web.Rep.Html.Input

type Rep InputType Source # 
Instance details

Defined in Web.Rep.Html.Input

type Rep InputType = D1 ('MetaData "InputType" "Web.Rep.Html.Input" "web-rep-0.10.0-14Ea0acHNZAIpwuRPiHk6A" 'False) (((C1 ('MetaCons "Slider" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [Attribute])) :+: (C1 ('MetaCons "SliderV" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [Attribute])) :+: C1 ('MetaCons "TextBox" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "TextBox'" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TextArea" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Int))) :+: (C1 ('MetaCons "ColorPicker" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ChooseFile" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "Dropdown" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [Text])) :+: (C1 ('MetaCons "DropdownMultiple" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [Text]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Char)) :+: C1 ('MetaCons "DropdownSum" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [Text])))) :+: ((C1 ('MetaCons "Datalist" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [Text]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Text)) :+: C1 ('MetaCons "Checkbox" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Bool))) :+: (C1 ('MetaCons "Toggle" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Bool) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe Text))) :+: C1 ('MetaCons "Button" 'PrefixI 'False) (U1 :: Type -> Type)))))