Safe Haskell | None |
---|---|
Language | Haskell98 |
Synopsis
- newtype DropdownViewEventResult en = DropdownViewEventResult {}
- type family DropdownViewEventResultType (en :: EventTag) :: * where ...
- data DropdownConfig t k = DropdownConfig {
- _dropdownConfig_setValue :: Event t k
- _dropdownConfig_attributes :: Dynamic t (Map Text Text)
- data Dropdown t k = Dropdown {
- _dropdown_value :: Dynamic t k
- _dropdown_change :: Event t k
- newtype FileInputConfig t = FileInputConfig {}
- data FileInput d t = FileInput {
- _fileInput_value :: Dynamic t [File]
- _fileInput_element :: RawInputElement d
- newtype CheckboxViewEventResult en = CheckboxViewEventResult {}
- type family CheckboxViewEventResultType (en :: EventTag) :: * where ...
- data Checkbox t = Checkbox {
- _checkbox_value :: Dynamic t Bool
- _checkbox_change :: Event t Bool
- data CheckboxConfig t = CheckboxConfig {}
- data TextArea t = TextArea {}
- data TextAreaConfig t = TextAreaConfig {}
- data RangeInput t = RangeInput {}
- data RangeInputConfig t = RangeInputConfig {}
- data TextInputConfig t = TextInputConfig {}
- data TextInput t = TextInput {}
- _textInput_element :: TextInput t -> HTMLInputElement
- textInput :: (DomBuilder t m, PostBuild t m, DomBuilderSpace m ~ GhcjsDomSpace) => TextInputConfig t -> m (TextInput t)
- textInputGetEnter :: Reflex t => TextInput t -> Event t ()
- keypress :: (Reflex t, HasDomEvent t e KeypressTag, DomEventType e KeypressTag ~ Word) => Key -> e -> Event t ()
- keydown :: (Reflex t, HasDomEvent t e KeydownTag, DomEventType e KeydownTag ~ Word) => Key -> e -> Event t ()
- keyup :: (Reflex t, HasDomEvent t e KeyupTag, DomEventType e KeyupTag ~ Word) => Key -> e -> Event t ()
- rangeInput :: (DomBuilder t m, PostBuild t m, DomBuilderSpace m ~ GhcjsDomSpace) => RangeInputConfig t -> m (RangeInput t)
- textArea :: (DomBuilder t m, PostBuild t m, DomBuilderSpace m ~ GhcjsDomSpace) => TextAreaConfig t -> m (TextArea t)
- checkbox :: (DomBuilder t m, PostBuild t m) => Bool -> CheckboxConfig t -> m (Checkbox t)
- regularToCheckboxViewEventType :: EventName t -> EventResultType t -> CheckboxViewEventResultType t
- checkboxView :: forall t m. (DomBuilder t m, DomBuilderSpace m ~ GhcjsDomSpace, PostBuild t m, MonadHold t m) => Dynamic t (Map Text Text) -> Dynamic t Bool -> m (Event t Bool)
- fileInput :: forall t m. (MonadIO m, MonadJSM m, MonadFix m, MonadHold t m, TriggerEvent t m, DomBuilder t m, PostBuild t m, DomBuilderSpace m ~ GhcjsDomSpace) => FileInputConfig t -> m (FileInput (DomBuilderSpace m) t)
- regularToDropdownViewEventType :: EventName t -> EventResultType t -> DropdownViewEventResultType t
- dropdown :: forall k t m. (DomBuilder t m, MonadFix m, MonadHold t m, PostBuild t m, Ord k) => k -> Dynamic t (Map k Text) -> DropdownConfig t k -> m (Dropdown t k)
- class HasValue a where
- class HasSetValue a where
- textAreaConfig_attributes :: forall t. Lens' (TextAreaConfig t) (Dynamic t (Map Text Text))
- textAreaConfig_initialValue :: forall t. Lens' (TextAreaConfig t) Text
- textAreaConfig_setValue :: forall t. Lens' (TextAreaConfig t) (Event t Text)
- textArea_element :: forall t. Lens' (TextArea t) HTMLTextAreaElement
- textArea_hasFocus :: forall t. Lens' (TextArea t) (Dynamic t Bool)
- textArea_input :: forall t. Lens' (TextArea t) (Event t Text)
- textArea_keypress :: forall t. Lens' (TextArea t) (Event t Word)
- textArea_value :: forall t. Lens' (TextArea t) (Dynamic t Text)
- textInputConfig_attributes :: forall t. Lens' (TextInputConfig t) (Dynamic t (Map Text Text))
- textInputConfig_initialValue :: forall t. Lens' (TextInputConfig t) Text
- textInputConfig_inputType :: forall t. Lens' (TextInputConfig t) Text
- textInputConfig_setValue :: forall t. Lens' (TextInputConfig t) (Event t Text)
- textInput_builderElement :: forall t. Lens' (TextInput t) (InputElement EventResult GhcjsDomSpace t)
- textInput_hasFocus :: forall t. Lens' (TextInput t) (Dynamic t Bool)
- textInput_input :: forall t. Lens' (TextInput t) (Event t Text)
- textInput_keydown :: forall t. Lens' (TextInput t) (Event t Word)
- textInput_keypress :: forall t. Lens' (TextInput t) (Event t Word)
- textInput_keyup :: forall t. Lens' (TextInput t) (Event t Word)
- textInput_value :: forall t. Lens' (TextInput t) (Dynamic t Text)
- rangeInputConfig_attributes :: forall t. Lens' (RangeInputConfig t) (Dynamic t (Map Text Text))
- rangeInputConfig_initialValue :: forall t. Lens' (RangeInputConfig t) Float
- rangeInputConfig_setValue :: forall t. Lens' (RangeInputConfig t) (Event t Float)
- rangeInput_element :: forall t. Lens' (RangeInput t) HTMLInputElement
- rangeInput_hasFocus :: forall t. Lens' (RangeInput t) (Dynamic t Bool)
- rangeInput_input :: forall t. Lens' (RangeInput t) (Event t Float)
- rangeInput_mouseup :: forall t. Lens' (RangeInput t) (Event t (Int, Int))
- rangeInput_value :: forall t. Lens' (RangeInput t) (Dynamic t Float)
- fileInputConfig_attributes :: forall t t. Iso (FileInputConfig t) (FileInputConfig t) (Dynamic t (Map Text Text)) (Dynamic t (Map Text Text))
- fileInput_element :: forall d t d. Lens (FileInput d t) (FileInput d t) (RawInputElement d) (RawInputElement d)
- fileInput_value :: forall d t t. Lens (FileInput d t) (FileInput d t) (Dynamic t [File]) (Dynamic t [File])
- dropdownConfig_attributes :: forall t k. Lens' (DropdownConfig t k) (Dynamic t (Map Text Text))
- dropdownConfig_setValue :: forall t k k. Lens (DropdownConfig t k) (DropdownConfig t k) (Event t k) (Event t k)
- dropdown_change :: forall t k. Lens' (Dropdown t k) (Event t k)
- dropdown_value :: forall t k. Lens' (Dropdown t k) (Dynamic t k)
- checkboxConfig_attributes :: forall t. Lens' (CheckboxConfig t) (Dynamic t (Map Text Text))
- checkboxConfig_setValue :: forall t. Lens' (CheckboxConfig t) (Event t Bool)
- checkbox_change :: forall t. Lens' (Checkbox t) (Event t Bool)
- checkbox_value :: forall t. Lens' (Checkbox t) (Dynamic t Bool)
- def :: Default a => a
- (&) :: a -> (a -> b) -> b
- (.~) :: ASetter s t a b -> b -> s -> t
Documentation
newtype DropdownViewEventResult en Source #
type family DropdownViewEventResultType (en :: EventTag) :: * where ... Source #
data DropdownConfig t k Source #
DropdownConfig | |
|
Instances
Reflex t => Default (DropdownConfig t k2) Source # | |
Defined in Reflex.Dom.Widget.Input def :: DropdownConfig t k2 # | |
HasAttributes (DropdownConfig t k2) Source # | |
Defined in Reflex.Dom.Widget.Input type Attrs (DropdownConfig t k2) :: * Source # attributes :: Lens' (DropdownConfig t k2) (Attrs (DropdownConfig t k2)) Source # | |
HasSetValue (DropdownConfig t k2) Source # | |
Defined in Reflex.Dom.Widget.Input type SetValue (DropdownConfig t k2) :: * Source # setValue :: Lens' (DropdownConfig t k2) (SetValue (DropdownConfig t k2)) Source # | |
type Attrs (DropdownConfig t k2) Source # | |
Defined in Reflex.Dom.Widget.Input | |
type SetValue (DropdownConfig t k2) Source # | |
Defined in Reflex.Dom.Widget.Input |
Dropdown | |
|
newtype FileInputConfig t Source #
Instances
Reflex t => Default (FileInputConfig t) Source # | |
Defined in Reflex.Dom.Widget.Input def :: FileInputConfig t # | |
HasAttributes (FileInputConfig t) Source # | |
Defined in Reflex.Dom.Widget.Input type Attrs (FileInputConfig t) :: * Source # attributes :: Lens' (FileInputConfig t) (Attrs (FileInputConfig t)) Source # | |
type Attrs (FileInputConfig t) Source # | |
Defined in Reflex.Dom.Widget.Input |
newtype CheckboxViewEventResult en Source #
type family CheckboxViewEventResultType (en :: EventTag) :: * where ... Source #
Checkbox | |
|
data CheckboxConfig t Source #
Instances
Reflex t => Default (CheckboxConfig t) Source # | |
Defined in Reflex.Dom.Widget.Input def :: CheckboxConfig t # | |
HasAttributes (CheckboxConfig t) Source # | |
Defined in Reflex.Dom.Widget.Input type Attrs (CheckboxConfig t) :: * Source # attributes :: Lens' (CheckboxConfig t) (Attrs (CheckboxConfig t)) Source # | |
HasSetValue (CheckboxConfig t) Source # | |
Defined in Reflex.Dom.Widget.Input type SetValue (CheckboxConfig t) :: * Source # setValue :: Lens' (CheckboxConfig t) (SetValue (CheckboxConfig t)) Source # | |
type Attrs (CheckboxConfig t) Source # | |
Defined in Reflex.Dom.Widget.Input | |
type SetValue (CheckboxConfig t) Source # | |
Defined in Reflex.Dom.Widget.Input |
data TextAreaConfig t Source #
Instances
Reflex t => Default (TextAreaConfig t) Source # | |
Defined in Reflex.Dom.Widget.Input def :: TextAreaConfig t # | |
HasAttributes (TextAreaConfig t) Source # | |
Defined in Reflex.Dom.Widget.Input type Attrs (TextAreaConfig t) :: * Source # attributes :: Lens' (TextAreaConfig t) (Attrs (TextAreaConfig t)) Source # | |
HasSetValue (TextAreaConfig t) Source # | |
Defined in Reflex.Dom.Widget.Input type SetValue (TextAreaConfig t) :: * Source # setValue :: Lens' (TextAreaConfig t) (SetValue (TextAreaConfig t)) Source # | |
type Attrs (TextAreaConfig t) Source # | |
Defined in Reflex.Dom.Widget.Input | |
type SetValue (TextAreaConfig t) Source # | |
Defined in Reflex.Dom.Widget.Input |
data RangeInput t Source #
RangeInput | |
|
Instances
HasValue (RangeInput t) Source # | |
Defined in Reflex.Dom.Widget.Input type Value (RangeInput t) :: * Source # value :: RangeInput t -> Value (RangeInput t) Source # | |
type Value (RangeInput t) Source # | |
Defined in Reflex.Dom.Widget.Input |
data RangeInputConfig t Source #
Instances
Reflex t => Default (RangeInputConfig t) Source # | |
Defined in Reflex.Dom.Widget.Input def :: RangeInputConfig t # | |
HasAttributes (RangeInputConfig t) Source # | |
Defined in Reflex.Dom.Widget.Input type Attrs (RangeInputConfig t) :: * Source # attributes :: Lens' (RangeInputConfig t) (Attrs (RangeInputConfig t)) Source # | |
HasSetValue (RangeInputConfig t) Source # | |
Defined in Reflex.Dom.Widget.Input type SetValue (RangeInputConfig t) :: * Source # setValue :: Lens' (RangeInputConfig t) (SetValue (RangeInputConfig t)) Source # | |
type Attrs (RangeInputConfig t) Source # | |
Defined in Reflex.Dom.Widget.Input | |
type SetValue (RangeInputConfig t) Source # | |
Defined in Reflex.Dom.Widget.Input |
data TextInputConfig t Source #
Instances
Reflex t => Default (TextInputConfig t) Source # | |
Defined in Reflex.Dom.Widget.Input def :: TextInputConfig t # | |
HasAttributes (TextInputConfig t) Source # | |
Defined in Reflex.Dom.Widget.Input type Attrs (TextInputConfig t) :: * Source # attributes :: Lens' (TextInputConfig t) (Attrs (TextInputConfig t)) Source # | |
HasSetValue (TextInputConfig t) Source # | |
Defined in Reflex.Dom.Widget.Input type SetValue (TextInputConfig t) :: * Source # setValue :: Lens' (TextInputConfig t) (SetValue (TextInputConfig t)) Source # | |
type Attrs (TextInputConfig t) Source # | |
Defined in Reflex.Dom.Widget.Input | |
type SetValue (TextInputConfig t) Source # | |
Defined in Reflex.Dom.Widget.Input |
Instances
Reflex t => HasDomEvent (t :: k) (TextInput t) en Source # | |
Defined in Reflex.Dom.Widget.Input type DomEventType (TextInput t) en :: * Source # | |
HasValue (TextInput t) Source # | |
type Value (TextInput t) Source # | |
Defined in Reflex.Dom.Widget.Input | |
type DomEventType (TextInput t) en Source # | |
Defined in Reflex.Dom.Widget.Input |
textInput :: (DomBuilder t m, PostBuild t m, DomBuilderSpace m ~ GhcjsDomSpace) => TextInputConfig t -> m (TextInput t) Source #
Create an input whose value is a string. By default, the "type" attribute is set to "text", but it can be changed using the _textInputConfig_inputType field. Note that only types for which the value is always a string will work - types whose value may be null will not work properly with this widget.
textInputGetEnter :: Reflex t => TextInput t -> Event t () Source #
Deprecated: Use 'keypress Enter' instead
keypress :: (Reflex t, HasDomEvent t e KeypressTag, DomEventType e KeypressTag ~ Word) => Key -> e -> Event t () Source #
keydown :: (Reflex t, HasDomEvent t e KeydownTag, DomEventType e KeydownTag ~ Word) => Key -> e -> Event t () Source #
keyup :: (Reflex t, HasDomEvent t e KeyupTag, DomEventType e KeyupTag ~ Word) => Key -> e -> Event t () Source #
rangeInput :: (DomBuilder t m, PostBuild t m, DomBuilderSpace m ~ GhcjsDomSpace) => RangeInputConfig t -> m (RangeInput t) Source #
Create an input whose value is a float. https://www.w3.org/wiki/HTML/Elements/input/range
textArea :: (DomBuilder t m, PostBuild t m, DomBuilderSpace m ~ GhcjsDomSpace) => TextAreaConfig t -> m (TextArea t) Source #
checkbox :: (DomBuilder t m, PostBuild t m) => Bool -> CheckboxConfig t -> m (Checkbox t) Source #
Create an editable checkbox Note: if the "type" or "checked" attributes are provided as attributes, they will be ignored
regularToCheckboxViewEventType :: EventName t -> EventResultType t -> CheckboxViewEventResultType t Source #
checkboxView :: forall t m. (DomBuilder t m, DomBuilderSpace m ~ GhcjsDomSpace, PostBuild t m, MonadHold t m) => Dynamic t (Map Text Text) -> Dynamic t Bool -> m (Event t Bool) Source #
fileInput :: forall t m. (MonadIO m, MonadJSM m, MonadFix m, MonadHold t m, TriggerEvent t m, DomBuilder t m, PostBuild t m, DomBuilderSpace m ~ GhcjsDomSpace) => FileInputConfig t -> m (FileInput (DomBuilderSpace m) t) Source #
regularToDropdownViewEventType :: EventName t -> EventResultType t -> DropdownViewEventResultType t Source #
dropdown :: forall k t m. (DomBuilder t m, MonadFix m, MonadHold t m, PostBuild t m, Ord k) => k -> Dynamic t (Map k Text) -> DropdownConfig t k -> m (Dropdown t k) Source #
Create a dropdown box The first argument gives the initial value of the dropdown; if it is not present in the map of options provided, it will be added with an empty string as its text
class HasValue a where Source #
Instances
HasValue (Checkbox t) Source # | |
HasValue (TextArea t) Source # | |
HasValue (RangeInput t) Source # | |
Defined in Reflex.Dom.Widget.Input type Value (RangeInput t) :: * Source # value :: RangeInput t -> Value (RangeInput t) Source # | |
HasValue (TextInput t) Source # | |
HasValue (Dropdown t k2) Source # | |
HasValue (FileInput d t) Source # | |
HasValue (TextAreaElement er d t) Source # | |
Defined in Reflex.Dom.Widget.Input type Value (TextAreaElement er d t) :: * Source # value :: TextAreaElement er d t -> Value (TextAreaElement er d t) Source # | |
HasValue (InputElement er d t) Source # | |
Defined in Reflex.Dom.Widget.Input type Value (InputElement er d t) :: * Source # value :: InputElement er d t -> Value (InputElement er d t) Source # |
class HasSetValue a where Source #
Instances
textAreaConfig_attributes :: forall t. Lens' (TextAreaConfig t) (Dynamic t (Map Text Text)) Source #
textAreaConfig_initialValue :: forall t. Lens' (TextAreaConfig t) Text Source #
textAreaConfig_setValue :: forall t. Lens' (TextAreaConfig t) (Event t Text) Source #
textArea_element :: forall t. Lens' (TextArea t) HTMLTextAreaElement Source #
textInputConfig_attributes :: forall t. Lens' (TextInputConfig t) (Dynamic t (Map Text Text)) Source #
textInputConfig_initialValue :: forall t. Lens' (TextInputConfig t) Text Source #
textInputConfig_inputType :: forall t. Lens' (TextInputConfig t) Text Source #
textInputConfig_setValue :: forall t. Lens' (TextInputConfig t) (Event t Text) Source #
textInput_builderElement :: forall t. Lens' (TextInput t) (InputElement EventResult GhcjsDomSpace t) Source #
rangeInputConfig_attributes :: forall t. Lens' (RangeInputConfig t) (Dynamic t (Map Text Text)) Source #
rangeInputConfig_initialValue :: forall t. Lens' (RangeInputConfig t) Float Source #
rangeInputConfig_setValue :: forall t. Lens' (RangeInputConfig t) (Event t Float) Source #
rangeInput_element :: forall t. Lens' (RangeInput t) HTMLInputElement Source #
rangeInput_hasFocus :: forall t. Lens' (RangeInput t) (Dynamic t Bool) Source #
rangeInput_input :: forall t. Lens' (RangeInput t) (Event t Float) Source #
rangeInput_mouseup :: forall t. Lens' (RangeInput t) (Event t (Int, Int)) Source #
rangeInput_value :: forall t. Lens' (RangeInput t) (Dynamic t Float) Source #
fileInputConfig_attributes :: forall t t. Iso (FileInputConfig t) (FileInputConfig t) (Dynamic t (Map Text Text)) (Dynamic t (Map Text Text)) Source #
fileInput_element :: forall d t d. Lens (FileInput d t) (FileInput d t) (RawInputElement d) (RawInputElement d) Source #
fileInput_value :: forall d t t. Lens (FileInput d t) (FileInput d t) (Dynamic t [File]) (Dynamic t [File]) Source #
dropdownConfig_attributes :: forall t k. Lens' (DropdownConfig t k) (Dynamic t (Map Text Text)) Source #
dropdownConfig_setValue :: forall t k k. Lens (DropdownConfig t k) (DropdownConfig t k) (Event t k) (Event t k) Source #
checkboxConfig_attributes :: forall t. Lens' (CheckboxConfig t) (Dynamic t (Map Text Text)) Source #
checkboxConfig_setValue :: forall t. Lens' (CheckboxConfig t) (Event t Bool) Source #
(.~) :: ASetter s t a b -> b -> s -> t infixr 4 #
Replace the target of a Lens
or all of the targets of a Setter
or Traversal
with a constant value.
This is an infix version of set
, provided for consistency with (.=
).
f<$
a ≡mapped
.~
f$
a
>>>
(a,b,c,d) & _4 .~ e
(a,b,c,e)
>>>
(42,"world") & _1 .~ "hello"
("hello","world")
>>>
(a,b) & both .~ c
(c,c)
(.~
) ::Setter
s t a b -> b -> s -> t (.~
) ::Iso
s t a b -> b -> s -> t (.~
) ::Lens
s t a b -> b -> s -> t (.~
) ::Traversal
s t a b -> b -> s -> t