Safe Haskell | None |
---|---|
Language | Haskell98 |
Reflex.Dom.Widget.Input
Synopsis
- class HasValue a where
- type family Value a
- data TextArea (t :: k) = TextArea {}
- data TextInput (t :: k1) = TextInput {}
- _textInput_element :: forall {k1} (t :: k1). TextInput t -> HTMLInputElement
- data TextInputConfig (t :: k) = TextInputConfig {}
- textInput :: (DomBuilder t m, PostBuild t m, DomBuilderSpace m ~ GhcjsDomSpace) => TextInputConfig t -> m (TextInput t)
- textInputGetEnter :: forall {k} (t :: k). Reflex t => TextInput t -> Event t ()
- keypress :: forall {k} (t :: k) e. (Reflex t, HasDomEvent t e 'KeypressTag, DomEventType e 'KeypressTag ~ Word) => Key -> e -> Event t ()
- keydown :: forall {k} (t :: k) e. (Reflex t, HasDomEvent t e 'KeydownTag, DomEventType e 'KeydownTag ~ Word) => Key -> e -> Event t ()
- keyup :: forall {k} (t :: k) e. (Reflex t, HasDomEvent t e 'KeyupTag, DomEventType e 'KeyupTag ~ Word) => Key -> e -> Event t ()
- data RangeInputConfig (t :: k) = RangeInputConfig {}
- data RangeInput (t :: k) = RangeInput {}
- rangeInput :: (DomBuilder t m, PostBuild t m, DomBuilderSpace m ~ GhcjsDomSpace) => RangeInputConfig t -> m (RangeInput t)
- data TextAreaConfig (t :: k) = TextAreaConfig {}
- textArea :: (DomBuilder t m, PostBuild t m, DomBuilderSpace m ~ GhcjsDomSpace) => TextAreaConfig t -> m (TextArea t)
- data CheckboxConfig (t :: k) = CheckboxConfig {}
- data Checkbox (t :: k) = Checkbox {
- _checkbox_value :: Dynamic t Bool
- _checkbox_change :: Event t Bool
- checkbox :: (DomBuilder t m, PostBuild t m) => Bool -> CheckboxConfig t -> m (Checkbox t)
- checkboxView :: (DomBuilder t m, DomBuilderSpace m ~ GhcjsDomSpace, PostBuild t m) => Dynamic t (Map Text Text) -> Dynamic t Bool -> m (Event t Bool)
- type family CheckboxViewEventResultType (en :: EventTag) where ...
- regularToCheckboxViewEventType :: forall (t :: EventTag). EventName t -> EventResultType t -> CheckboxViewEventResultType t
- newtype CheckboxViewEventResult (en :: EventTag) = CheckboxViewEventResult {}
- data FileInput (d :: k) (t :: k1) = FileInput {
- _fileInput_value :: Dynamic t [File]
- _fileInput_element :: RawInputElement d
- newtype FileInputConfig (t :: k) = FileInputConfig {}
- fileInput :: forall t m. (MonadIO m, DomBuilder t m, PostBuild t m, DomBuilderSpace m ~ GhcjsDomSpace) => FileInputConfig t -> m (FileInput (DomBuilderSpace m) t)
- data Dropdown (t :: k) k1 = Dropdown {
- _dropdown_value :: Dynamic t k1
- _dropdown_change :: Event t k1
- data DropdownConfig (t :: k) k1 = DropdownConfig {
- _dropdownConfig_setValue :: Event t k1
- _dropdownConfig_attributes :: Dynamic t (Map Text Text)
- type family DropdownViewEventResultType (en :: EventTag) where ...
- newtype DropdownViewEventResult (en :: EventTag) = DropdownViewEventResult {}
- regularToDropdownViewEventType :: forall (t :: EventTag). 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)
- textAreaConfig_attributes :: forall k (t :: k) f. Functor f => (Dynamic t (Map Text Text) -> f (Dynamic t (Map Text Text))) -> TextAreaConfig t -> f (TextAreaConfig t)
- textInputConfig_attributes :: forall k (t :: k) f. Functor f => (Dynamic t (Map Text Text) -> f (Dynamic t (Map Text Text))) -> TextInputConfig t -> f (TextInputConfig t)
- rangeInputConfig_attributes :: forall k (t :: k) f. Functor f => (Dynamic t (Map Text Text) -> f (Dynamic t (Map Text Text))) -> RangeInputConfig t -> f (RangeInputConfig t)
- dropdownConfig_attributes :: forall k1 (t :: k1) k2 f. Functor f => (Dynamic t (Map Text Text) -> f (Dynamic t (Map Text Text))) -> DropdownConfig t k2 -> f (DropdownConfig t k2)
- checkboxConfig_attributes :: forall k (t :: k) f. Functor f => (Dynamic t (Map Text Text) -> f (Dynamic t (Map Text Text))) -> CheckboxConfig t -> f (CheckboxConfig t)
- fileInputConfig_attributes :: forall k1 (t1 :: k1) k2 (t2 :: k2) p f. (Profunctor p, Functor f) => p (Dynamic t1 (Map Text Text)) (f (Dynamic t2 (Map Text Text))) -> p (FileInputConfig t1) (f (FileInputConfig t2))
- textAreaConfig_setValue :: forall k (t :: k) f. Functor f => (Event t Text -> f (Event t Text)) -> TextAreaConfig t -> f (TextAreaConfig t)
- textInputConfig_setValue :: forall k (t :: k) f. Functor f => (Event t Text -> f (Event t Text)) -> TextInputConfig t -> f (TextInputConfig t)
- rangeInputConfig_setValue :: forall k (t :: k) f. Functor f => (Event t Float -> f (Event t Float)) -> RangeInputConfig t -> f (RangeInputConfig t)
- dropdownConfig_setValue :: forall k1 (t :: k1) k2 k3 f. Functor f => (Event t k2 -> f (Event t k3)) -> DropdownConfig t k2 -> f (DropdownConfig t k3)
- checkboxConfig_setValue :: forall k (t :: k) f. Functor f => (Event t Bool -> f (Event t Bool)) -> CheckboxConfig t -> f (CheckboxConfig t)
- textAreaConfig_initialValue :: forall k (t :: k) f. Functor f => (Text -> f Text) -> TextAreaConfig t -> f (TextAreaConfig t)
- textArea_element :: forall k (t :: k) f. Functor f => (HTMLTextAreaElement -> f HTMLTextAreaElement) -> TextArea t -> f (TextArea t)
- textArea_hasFocus :: forall k (t :: k) f. Functor f => (Dynamic t Bool -> f (Dynamic t Bool)) -> TextArea t -> f (TextArea t)
- textArea_input :: forall k (t :: k) f. Functor f => (Event t Text -> f (Event t Text)) -> TextArea t -> f (TextArea t)
- textArea_keypress :: forall k (t :: k) f. Functor f => (Event t Word -> f (Event t Word)) -> TextArea t -> f (TextArea t)
- textArea_value :: forall k (t :: k) f. Functor f => (Dynamic t Text -> f (Dynamic t Text)) -> TextArea t -> f (TextArea t)
- textInputConfig_initialValue :: forall k (t :: k) f. Functor f => (Text -> f Text) -> TextInputConfig t -> f (TextInputConfig t)
- textInputConfig_inputType :: forall k (t :: k) f. Functor f => (Text -> f Text) -> TextInputConfig t -> f (TextInputConfig t)
- textInput_builderElement :: forall k1 (t :: k1) f. Functor f => (InputElement EventResult GhcjsDomSpace t -> f (InputElement EventResult GhcjsDomSpace t)) -> TextInput t -> f (TextInput t)
- textInput_hasFocus :: forall k1 (t :: k1) f. Functor f => (Dynamic t Bool -> f (Dynamic t Bool)) -> TextInput t -> f (TextInput t)
- textInput_input :: forall k1 (t :: k1) f. Functor f => (Event t Text -> f (Event t Text)) -> TextInput t -> f (TextInput t)
- textInput_keydown :: forall k1 (t :: k1) f. Functor f => (Event t Word -> f (Event t Word)) -> TextInput t -> f (TextInput t)
- textInput_keypress :: forall k1 (t :: k1) f. Functor f => (Event t Word -> f (Event t Word)) -> TextInput t -> f (TextInput t)
- textInput_keyup :: forall k1 (t :: k1) f. Functor f => (Event t Word -> f (Event t Word)) -> TextInput t -> f (TextInput t)
- textInput_value :: forall k1 (t :: k1) f. Functor f => (Dynamic t Text -> f (Dynamic t Text)) -> TextInput t -> f (TextInput t)
- rangeInputConfig_initialValue :: forall k (t :: k) f. Functor f => (Float -> f Float) -> RangeInputConfig t -> f (RangeInputConfig t)
- rangeInput_element :: forall k (t :: k) f. Functor f => (HTMLInputElement -> f HTMLInputElement) -> RangeInput t -> f (RangeInput t)
- rangeInput_hasFocus :: forall k (t :: k) f. Functor f => (Dynamic t Bool -> f (Dynamic t Bool)) -> RangeInput t -> f (RangeInput t)
- rangeInput_input :: forall k (t :: k) f. Functor f => (Event t Float -> f (Event t Float)) -> RangeInput t -> f (RangeInput t)
- rangeInput_mouseup :: forall k (t :: k) f. Functor f => (Event t (Int, Int) -> f (Event t (Int, Int))) -> RangeInput t -> f (RangeInput t)
- rangeInput_value :: forall k (t :: k) f. Functor f => (Dynamic t Float -> f (Dynamic t Float)) -> RangeInput t -> f (RangeInput t)
- fileInput_element :: forall k1 (d1 :: k1) k2 (t :: k2) k3 (d2 :: k3) f. Functor f => (RawInputElement d1 -> f (RawInputElement d2)) -> FileInput d1 t -> f (FileInput d2 t)
- fileInput_value :: forall k1 (d :: k1) k2 (t1 :: k2) k3 (t2 :: k3) f. Functor f => (Dynamic t1 [File] -> f (Dynamic t2 [File])) -> FileInput d t1 -> f (FileInput d t2)
- dropdown_change :: forall k1 (t :: k1) k2 f. Functor f => (Event t k2 -> f (Event t k2)) -> Dropdown t k2 -> f (Dropdown t k2)
- dropdown_value :: forall k1 (t :: k1) k2 f. Functor f => (Dynamic t k2 -> f (Dynamic t k2)) -> Dropdown t k2 -> f (Dropdown t k2)
- checkbox_change :: forall k (t :: k) f. Functor f => (Event t Bool -> f (Event t Bool)) -> Checkbox t -> f (Checkbox t)
- checkbox_value :: forall k (t :: k) f. Functor f => (Dynamic t Bool -> f (Dynamic t Bool)) -> Checkbox t -> f (Checkbox t)
- def :: Default a => a
- (&) :: a -> (a -> b) -> b
- (.~) :: ASetter s t a b -> b -> s -> t
Documentation
class HasValue a where Source #
Instances
HasValue (Checkbox t) Source # | |||||
HasValue (RangeInput t) Source # | |||||
Defined in Reflex.Dom.Widget.Input Associated Types
Methods value :: RangeInput t -> Value (RangeInput t) Source # | |||||
HasValue (TextArea t) Source # | |||||
HasValue (TextInput t) Source # | |||||
HasValue (Dropdown t k2) Source # | |||||
HasValue (FileInput d t) Source # | |||||
HasValue (InputElement er d t) Source # | |||||
Defined in Reflex.Dom.Widget.Input Associated Types
Methods value :: InputElement er d t -> Value (InputElement er d t) Source # | |||||
HasValue (TextAreaElement er d t) Source # | |||||
Defined in Reflex.Dom.Widget.Input Associated Types
Methods value :: TextAreaElement er d t -> Value (TextAreaElement er d t) Source # |
Instances
type Value (Checkbox t) Source # | |
Defined in Reflex.Dom.Widget.Input | |
type Value (RangeInput t) Source # | |
Defined in Reflex.Dom.Widget.Input | |
type Value (TextArea t) Source # | |
Defined in Reflex.Dom.Widget.Input | |
type Value (TextInput t) Source # | |
Defined in Reflex.Dom.Widget.Input | |
type Value (Dropdown t k2) Source # | |
Defined in Reflex.Dom.Widget.Input | |
type Value (FileInput d t) Source # | |
Defined in Reflex.Dom.Widget.Input | |
type Value (InputElement er d t) Source # | |
Defined in Reflex.Dom.Widget.Input | |
type Value (TextAreaElement er d t) Source # | |
Defined in Reflex.Dom.Widget.Input |
data TextArea (t :: k) Source #
Deprecated: Use textAreaElement
directly
Constructors
TextArea | Deprecated: Use |
Fields
|
data TextInput (t :: k1) Source #
Deprecated: Use inputElement
directly
Constructors
TextInput | Deprecated: Use |
Fields
|
Instances
Reflex t => HasDomEvent (t :: k1) (TextInput t) en Source # | |||||
Defined in Reflex.Dom.Widget.Input Associated Types
| |||||
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_element :: forall {k1} (t :: k1). TextInput t -> HTMLInputElement Source #
Deprecated: Use inputElement
directly
data TextInputConfig (t :: k) Source #
Deprecated: Use inputElement
directly
Constructors
TextInputConfig | Deprecated: Use |
Instances
Reflex t => Default (TextInputConfig t) Source # | |||||
Defined in Reflex.Dom.Widget.Input Methods def :: TextInputConfig t # | |||||
HasSetValue (TextInputConfig t) Source # | |||||
Defined in Reflex.Dom.Widget.Input Associated Types
Methods setValue :: Lens' (TextInputConfig t) (SetValue (TextInputConfig t)) Source # | |||||
HasAttributes (TextInputConfig t) Source # | |||||
Defined in Reflex.Dom.Widget.Input Associated Types
Methods attributes :: Lens' (TextInputConfig t) (Attrs (TextInputConfig t)) Source # | |||||
type SetValue (TextInputConfig t) Source # | |||||
Defined in Reflex.Dom.Widget.Input | |||||
type Attrs (TextInputConfig t) Source # | |||||
Defined in Reflex.Dom.Widget.Input |
textInput :: (DomBuilder t m, PostBuild t m, DomBuilderSpace m ~ GhcjsDomSpace) => TextInputConfig t -> m (TextInput t) Source #
Deprecated: Use inputElement
directly
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 :: forall {k} (t :: k). Reflex t => TextInput t -> Event t () Source #
Deprecated: Use 'keypress Enter' instead
keypress :: forall {k} (t :: k) e. (Reflex t, HasDomEvent t e 'KeypressTag, DomEventType e 'KeypressTag ~ Word) => Key -> e -> Event t () Source #
keydown :: forall {k} (t :: k) e. (Reflex t, HasDomEvent t e 'KeydownTag, DomEventType e 'KeydownTag ~ Word) => Key -> e -> Event t () Source #
keyup :: forall {k} (t :: k) e. (Reflex t, HasDomEvent t e 'KeyupTag, DomEventType e 'KeyupTag ~ Word) => Key -> e -> Event t () Source #
data RangeInputConfig (t :: k) Source #
Constructors
RangeInputConfig | |
Fields |
Instances
Reflex t => Default (RangeInputConfig t) Source # | |||||
Defined in Reflex.Dom.Widget.Input Methods def :: RangeInputConfig t # | |||||
HasSetValue (RangeInputConfig t) Source # | |||||
Defined in Reflex.Dom.Widget.Input Associated Types
Methods setValue :: Lens' (RangeInputConfig t) (SetValue (RangeInputConfig t)) Source # | |||||
HasAttributes (RangeInputConfig t) Source # | |||||
Defined in Reflex.Dom.Widget.Input Associated Types
Methods attributes :: Lens' (RangeInputConfig t) (Attrs (RangeInputConfig t)) Source # | |||||
type SetValue (RangeInputConfig t) Source # | |||||
Defined in Reflex.Dom.Widget.Input | |||||
type Attrs (RangeInputConfig t) Source # | |||||
Defined in Reflex.Dom.Widget.Input |
data RangeInput (t :: k) Source #
Constructors
RangeInput | |
Fields
|
Instances
HasValue (RangeInput t) Source # | |||||
Defined in Reflex.Dom.Widget.Input Associated Types
Methods value :: RangeInput t -> Value (RangeInput t) Source # | |||||
type Value (RangeInput t) Source # | |||||
Defined in Reflex.Dom.Widget.Input |
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
data TextAreaConfig (t :: k) Source #
Deprecated: Use textAreaElement
directly
Constructors
TextAreaConfig | Deprecated: Use |
Fields |
Instances
Reflex t => Default (TextAreaConfig t) Source # | |||||
Defined in Reflex.Dom.Widget.Input Methods def :: TextAreaConfig t # | |||||
HasSetValue (TextAreaConfig t) Source # | |||||
Defined in Reflex.Dom.Widget.Input Associated Types
Methods setValue :: Lens' (TextAreaConfig t) (SetValue (TextAreaConfig t)) Source # | |||||
HasAttributes (TextAreaConfig t) Source # | |||||
Defined in Reflex.Dom.Widget.Input Associated Types
Methods attributes :: Lens' (TextAreaConfig t) (Attrs (TextAreaConfig t)) Source # | |||||
type SetValue (TextAreaConfig t) Source # | |||||
Defined in Reflex.Dom.Widget.Input | |||||
type Attrs (TextAreaConfig t) Source # | |||||
Defined in Reflex.Dom.Widget.Input |
textArea :: (DomBuilder t m, PostBuild t m, DomBuilderSpace m ~ GhcjsDomSpace) => TextAreaConfig t -> m (TextArea t) Source #
Deprecated: Use textAreaElement
directly
data CheckboxConfig (t :: k) Source #
Deprecated: Use inputElement
directly
Constructors
CheckboxConfig | Deprecated: Use |
Fields |
Instances
Reflex t => Default (CheckboxConfig t) Source # | |||||
Defined in Reflex.Dom.Widget.Input Methods def :: CheckboxConfig t # | |||||
HasSetValue (CheckboxConfig t) Source # | |||||
Defined in Reflex.Dom.Widget.Input Associated Types
Methods setValue :: Lens' (CheckboxConfig t) (SetValue (CheckboxConfig t)) Source # | |||||
HasAttributes (CheckboxConfig t) Source # | |||||
Defined in Reflex.Dom.Widget.Input Associated Types
Methods attributes :: Lens' (CheckboxConfig t) (Attrs (CheckboxConfig t)) Source # | |||||
type SetValue (CheckboxConfig t) Source # | |||||
Defined in Reflex.Dom.Widget.Input | |||||
type Attrs (CheckboxConfig t) Source # | |||||
Defined in Reflex.Dom.Widget.Input |
data Checkbox (t :: k) Source #
Deprecated: Use inputElement
directly
Constructors
Checkbox | Deprecated: Use |
Fields
|
checkbox :: (DomBuilder t m, PostBuild t m) => Bool -> CheckboxConfig t -> m (Checkbox t) Source #
Deprecated: Use inputElement
directly
Create an editable checkbox Note: if the "type" or "checked" attributes are provided as attributes, they will be ignored
checkboxView :: (DomBuilder t m, DomBuilderSpace m ~ GhcjsDomSpace, PostBuild t m) => Dynamic t (Map Text Text) -> Dynamic t Bool -> m (Event t Bool) Source #
Deprecated: Use inputElement
directly
Create a view only checkbox
type family CheckboxViewEventResultType (en :: EventTag) where ... Source #
Deprecated: Use inputElement
directly
Equations
CheckboxViewEventResultType 'ClickTag = Bool | |
CheckboxViewEventResultType t = EventResultType t |
regularToCheckboxViewEventType :: forall (t :: EventTag). EventName t -> EventResultType t -> CheckboxViewEventResultType t Source #
Deprecated: Use inputElement
directly
newtype CheckboxViewEventResult (en :: EventTag) Source #
Deprecated: Use inputElement
directly
Constructors
CheckboxViewEventResult | Deprecated: Use |
Fields |
data FileInput (d :: k) (t :: k1) Source #
Deprecated: Use inputElement
directly
Constructors
FileInput | Deprecated: Use |
Fields
|
newtype FileInputConfig (t :: k) Source #
Deprecated: Use inputElement
directly
Constructors
FileInputConfig | Deprecated: Use |
Fields |
Instances
Reflex t => Default (FileInputConfig t) Source # | |||||
Defined in Reflex.Dom.Widget.Input Methods def :: FileInputConfig t # | |||||
HasAttributes (FileInputConfig t) Source # | |||||
Defined in Reflex.Dom.Widget.Input Associated Types
Methods attributes :: Lens' (FileInputConfig t) (Attrs (FileInputConfig t)) Source # | |||||
type Attrs (FileInputConfig t) Source # | |||||
Defined in Reflex.Dom.Widget.Input |
fileInput :: forall t m. (MonadIO m, DomBuilder t m, PostBuild t m, DomBuilderSpace m ~ GhcjsDomSpace) => FileInputConfig t -> m (FileInput (DomBuilderSpace m) t) Source #
Deprecated: Use inputElement
directly
data Dropdown (t :: k) k1 Source #
Constructors
Dropdown | |
Fields
|
data DropdownConfig (t :: k) k1 Source #
Constructors
DropdownConfig | |
Fields
|
Instances
Reflex t => Default (DropdownConfig t k2) Source # | |||||
Defined in Reflex.Dom.Widget.Input Methods def :: DropdownConfig t k2 # | |||||
HasSetValue (DropdownConfig t k2) Source # | |||||
Defined in Reflex.Dom.Widget.Input Associated Types
Methods setValue :: Lens' (DropdownConfig t k2) (SetValue (DropdownConfig t k2)) Source # | |||||
HasAttributes (DropdownConfig t k2) Source # | |||||
Defined in Reflex.Dom.Widget.Input Associated Types
Methods attributes :: Lens' (DropdownConfig t k2) (Attrs (DropdownConfig t k2)) Source # | |||||
type SetValue (DropdownConfig t k2) Source # | |||||
Defined in Reflex.Dom.Widget.Input | |||||
type Attrs (DropdownConfig t k2) Source # | |||||
Defined in Reflex.Dom.Widget.Input |
type family DropdownViewEventResultType (en :: EventTag) where ... Source #
Equations
DropdownViewEventResultType 'ChangeTag = Text | |
DropdownViewEventResultType t = EventResultType t |
newtype DropdownViewEventResult (en :: EventTag) Source #
Constructors
DropdownViewEventResult | |
Fields |
regularToDropdownViewEventType :: forall (t :: EventTag). 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
textAreaConfig_attributes :: forall k (t :: k) f. Functor f => (Dynamic t (Map Text Text) -> f (Dynamic t (Map Text Text))) -> TextAreaConfig t -> f (TextAreaConfig t) Source #
textInputConfig_attributes :: forall k (t :: k) f. Functor f => (Dynamic t (Map Text Text) -> f (Dynamic t (Map Text Text))) -> TextInputConfig t -> f (TextInputConfig t) Source #
rangeInputConfig_attributes :: forall k (t :: k) f. Functor f => (Dynamic t (Map Text Text) -> f (Dynamic t (Map Text Text))) -> RangeInputConfig t -> f (RangeInputConfig t) Source #
dropdownConfig_attributes :: forall k1 (t :: k1) k2 f. Functor f => (Dynamic t (Map Text Text) -> f (Dynamic t (Map Text Text))) -> DropdownConfig t k2 -> f (DropdownConfig t k2) Source #
checkboxConfig_attributes :: forall k (t :: k) f. Functor f => (Dynamic t (Map Text Text) -> f (Dynamic t (Map Text Text))) -> CheckboxConfig t -> f (CheckboxConfig t) Source #
fileInputConfig_attributes :: forall k1 (t1 :: k1) k2 (t2 :: k2) p f. (Profunctor p, Functor f) => p (Dynamic t1 (Map Text Text)) (f (Dynamic t2 (Map Text Text))) -> p (FileInputConfig t1) (f (FileInputConfig t2)) Source #
textAreaConfig_setValue :: forall k (t :: k) f. Functor f => (Event t Text -> f (Event t Text)) -> TextAreaConfig t -> f (TextAreaConfig t) Source #
textInputConfig_setValue :: forall k (t :: k) f. Functor f => (Event t Text -> f (Event t Text)) -> TextInputConfig t -> f (TextInputConfig t) Source #
rangeInputConfig_setValue :: forall k (t :: k) f. Functor f => (Event t Float -> f (Event t Float)) -> RangeInputConfig t -> f (RangeInputConfig t) Source #
dropdownConfig_setValue :: forall k1 (t :: k1) k2 k3 f. Functor f => (Event t k2 -> f (Event t k3)) -> DropdownConfig t k2 -> f (DropdownConfig t k3) Source #
checkboxConfig_setValue :: forall k (t :: k) f. Functor f => (Event t Bool -> f (Event t Bool)) -> CheckboxConfig t -> f (CheckboxConfig t) Source #
textAreaConfig_initialValue :: forall k (t :: k) f. Functor f => (Text -> f Text) -> TextAreaConfig t -> f (TextAreaConfig t) Source #
textArea_element :: forall k (t :: k) f. Functor f => (HTMLTextAreaElement -> f HTMLTextAreaElement) -> TextArea t -> f (TextArea t) Source #
textArea_hasFocus :: forall k (t :: k) f. Functor f => (Dynamic t Bool -> f (Dynamic t Bool)) -> TextArea t -> f (TextArea t) Source #
textArea_input :: forall k (t :: k) f. Functor f => (Event t Text -> f (Event t Text)) -> TextArea t -> f (TextArea t) Source #
textArea_keypress :: forall k (t :: k) f. Functor f => (Event t Word -> f (Event t Word)) -> TextArea t -> f (TextArea t) Source #
textArea_value :: forall k (t :: k) f. Functor f => (Dynamic t Text -> f (Dynamic t Text)) -> TextArea t -> f (TextArea t) Source #
textInputConfig_initialValue :: forall k (t :: k) f. Functor f => (Text -> f Text) -> TextInputConfig t -> f (TextInputConfig t) Source #
textInputConfig_inputType :: forall k (t :: k) f. Functor f => (Text -> f Text) -> TextInputConfig t -> f (TextInputConfig t) Source #
textInput_builderElement :: forall k1 (t :: k1) f. Functor f => (InputElement EventResult GhcjsDomSpace t -> f (InputElement EventResult GhcjsDomSpace t)) -> TextInput t -> f (TextInput t) Source #
textInput_hasFocus :: forall k1 (t :: k1) f. Functor f => (Dynamic t Bool -> f (Dynamic t Bool)) -> TextInput t -> f (TextInput t) Source #
textInput_input :: forall k1 (t :: k1) f. Functor f => (Event t Text -> f (Event t Text)) -> TextInput t -> f (TextInput t) Source #
textInput_keydown :: forall k1 (t :: k1) f. Functor f => (Event t Word -> f (Event t Word)) -> TextInput t -> f (TextInput t) Source #
textInput_keypress :: forall k1 (t :: k1) f. Functor f => (Event t Word -> f (Event t Word)) -> TextInput t -> f (TextInput t) Source #
textInput_keyup :: forall k1 (t :: k1) f. Functor f => (Event t Word -> f (Event t Word)) -> TextInput t -> f (TextInput t) Source #
textInput_value :: forall k1 (t :: k1) f. Functor f => (Dynamic t Text -> f (Dynamic t Text)) -> TextInput t -> f (TextInput t) Source #
rangeInputConfig_initialValue :: forall k (t :: k) f. Functor f => (Float -> f Float) -> RangeInputConfig t -> f (RangeInputConfig t) Source #
rangeInput_element :: forall k (t :: k) f. Functor f => (HTMLInputElement -> f HTMLInputElement) -> RangeInput t -> f (RangeInput t) Source #
rangeInput_hasFocus :: forall k (t :: k) f. Functor f => (Dynamic t Bool -> f (Dynamic t Bool)) -> RangeInput t -> f (RangeInput t) Source #
rangeInput_input :: forall k (t :: k) f. Functor f => (Event t Float -> f (Event t Float)) -> RangeInput t -> f (RangeInput t) Source #
rangeInput_mouseup :: forall k (t :: k) f. Functor f => (Event t (Int, Int) -> f (Event t (Int, Int))) -> RangeInput t -> f (RangeInput t) Source #
rangeInput_value :: forall k (t :: k) f. Functor f => (Dynamic t Float -> f (Dynamic t Float)) -> RangeInput t -> f (RangeInput t) Source #
fileInput_element :: forall k1 (d1 :: k1) k2 (t :: k2) k3 (d2 :: k3) f. Functor f => (RawInputElement d1 -> f (RawInputElement d2)) -> FileInput d1 t -> f (FileInput d2 t) Source #
fileInput_value :: forall k1 (d :: k1) k2 (t1 :: k2) k3 (t2 :: k3) f. Functor f => (Dynamic t1 [File] -> f (Dynamic t2 [File])) -> FileInput d t1 -> f (FileInput d t2) Source #
dropdown_change :: forall k1 (t :: k1) k2 f. Functor f => (Event t k2 -> f (Event t k2)) -> Dropdown t k2 -> f (Dropdown t k2) Source #
dropdown_value :: forall k1 (t :: k1) k2 f. Functor f => (Dynamic t k2 -> f (Dynamic t k2)) -> Dropdown t k2 -> f (Dropdown t k2) Source #
checkbox_change :: forall k (t :: k) f. Functor f => (Event t Bool -> f (Event t Bool)) -> Checkbox t -> f (Checkbox t) Source #
checkbox_value :: forall k (t :: k) f. Functor f => (Dynamic t Bool -> f (Dynamic t Bool)) -> Checkbox t -> f (Checkbox t) Source #
(&) :: a -> (a -> b) -> b infixl 1 #
&
is a reverse application operator. This provides notational
convenience. Its precedence is one higher than that of the forward
application operator $
, which allows &
to be nested in $
.
This is a version of
, where flip
id
id
is specialized from a -> a
to (a -> b) -> (a -> b)
which by the associativity of (->)
is (a -> b) -> a -> b
.
flipping this yields a -> (a -> b) -> b
which is the type signature of &
Examples
>>>
5 & (+1) & show
"6"
>>>
sqrt $ [1 / n^2 | n <- [1..1000]] & sum & (*6)
3.1406380562059946
Since: base-4.8.0.0
(.~) :: 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