Safe Haskell | None |
---|---|
Language | Haskell98 |
- data TextInput t = TextInput {}
- data TextInputConfig t = TextInputConfig {}
- textInput :: MonadWidget t m => TextInputConfig t -> m (TextInput t)
- textInputGetEnter :: Reflex t => TextInput t -> Event t ()
- data TextAreaConfig t = TextAreaConfig {}
- data TextArea t = TextArea {}
- textArea :: MonadWidget t m => TextAreaConfig t -> m (TextArea t)
- data CheckboxConfig t = CheckboxConfig {}
- data Checkbox t = Checkbox {
- _checkbox_value :: Dynamic t Bool
- checkbox :: MonadWidget t m => Bool -> CheckboxConfig t -> m (Checkbox t)
- checkboxView :: MonadWidget t m => Dynamic t (Map String String) -> Dynamic t Bool -> m (Event t Bool)
- data Dropdown t k = Dropdown {
- _dropdown_value :: Dynamic t k
- data DropdownConfig t k = DropdownConfig {}
- dropdown :: forall k t m. (MonadWidget t m, Ord k, Show k, Read k) => k -> Dynamic t (Map k String) -> DropdownConfig t k -> m (Dropdown t k)
- checkbox_value :: forall t t. Iso (Checkbox t) (Checkbox t) (Dynamic t Bool) (Dynamic t Bool)
- checkboxConfig_setValue :: forall t. Lens' (CheckboxConfig t) (Event t Bool)
- checkboxConfig_attributes :: forall t. Lens' (CheckboxConfig t) (Dynamic t (Map String String))
- dropdown_value :: forall t k t k. Iso (Dropdown t k) (Dropdown t k) (Dynamic t k) (Dynamic t k)
- dropdownConfig_setValue :: forall t k k. Lens (DropdownConfig t k) (DropdownConfig t k) (Event t k) (Event t k)
- dropdownConfig_attributes :: forall t k. Lens' (DropdownConfig t k) (Dynamic t (Map String String))
- textInput_value :: forall t. Lens' (TextInput t) (Dynamic t String)
- textInput_keyup :: forall t. Lens' (TextInput t) (Event t Int)
- textInput_keypress :: forall t. Lens' (TextInput t) (Event t Int)
- textInput_keydown :: forall t. Lens' (TextInput t) (Event t Int)
- textInput_hasFocus :: forall t. Lens' (TextInput t) (Dynamic t Bool)
- textInput_element :: forall t. Lens' (TextInput t) HTMLInputElement
- textInputConfig_setValue :: forall t. Lens' (TextInputConfig t) (Event t String)
- textInputConfig_inputType :: forall t. Lens' (TextInputConfig t) String
- textInputConfig_initialValue :: forall t. Lens' (TextInputConfig t) String
- textInputConfig_attributes :: forall t. Lens' (TextInputConfig t) (Dynamic t (Map String String))
- textArea_value :: forall t. Lens' (TextArea t) (Dynamic t String)
- textArea_keypress :: forall t. Lens' (TextArea t) (Event t Int)
- textArea_hasFocus :: forall t. Lens' (TextArea t) (Dynamic t Bool)
- textArea_element :: forall t. Lens' (TextArea t) HTMLTextAreaElement
- textAreaConfig_setValue :: forall t. Lens' (TextAreaConfig t) (Event t String)
- textAreaConfig_initialValue :: forall t. Lens' (TextAreaConfig t) String
- textAreaConfig_attributes :: forall t. Lens' (TextAreaConfig t) (Dynamic t (Map String String))
- class HasAttributes a where
- type Attrs a :: *
- attributes :: Lens' a (Attrs a)
- class HasSetValue a where
- class HasValue a where
- def :: Default a => a
- (&) :: a -> (a -> b) -> b
- (.~) :: ASetter s t a b -> b -> s -> t
Documentation
TextInput | |
|
data TextInputConfig t Source
Reflex t => Default (TextInputConfig t) Source | |
HasSetValue (TextInputConfig t) Source | |
HasAttributes (TextInputConfig t) Source | |
type SetValue (TextInputConfig t) = Event t String Source | |
type Attrs (TextInputConfig t) = Dynamic t (Map String String) Source |
textInput :: MonadWidget t m => TextInputConfig t -> m (TextInput t) Source
textInputGetEnter :: Reflex t => TextInput t -> Event t () Source
data TextAreaConfig t Source
Reflex t => Default (TextAreaConfig t) Source | |
HasSetValue (TextAreaConfig t) Source | |
HasAttributes (TextAreaConfig t) Source | |
type SetValue (TextAreaConfig t) = Event t String Source | |
type Attrs (TextAreaConfig t) = Dynamic t (Map String String) Source |
textArea :: MonadWidget t m => TextAreaConfig t -> m (TextArea t) Source
data CheckboxConfig t Source
Reflex t => Default (CheckboxConfig t) Source | |
HasSetValue (CheckboxConfig t) Source | |
HasAttributes (CheckboxConfig t) Source | |
type SetValue (CheckboxConfig t) = Event t Bool Source | |
type Attrs (CheckboxConfig t) = Dynamic t (Map String String) Source |
checkbox :: MonadWidget 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
checkboxView :: MonadWidget t m => Dynamic t (Map String String) -> Dynamic t Bool -> m (Event t Bool) Source
Dropdown | |
|
data DropdownConfig t k Source
DropdownConfig | |
|
(Reflex t, Ord k, Show k, Read k) => Default (DropdownConfig t k) Source | |
HasSetValue (DropdownConfig t k) Source | |
HasAttributes (DropdownConfig t k) Source | |
type SetValue (DropdownConfig t k) = Event t k Source | |
type Attrs (DropdownConfig t k) = Dynamic t (Map String String) Source |
dropdown :: forall k t m. (MonadWidget t m, Ord k, Show k, Read k) => k -> Dynamic t (Map k String) -> 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
checkbox_value :: forall t t. Iso (Checkbox t) (Checkbox t) (Dynamic t Bool) (Dynamic t Bool) Source
checkboxConfig_setValue :: forall t. Lens' (CheckboxConfig t) (Event t Bool) Source
checkboxConfig_attributes :: forall t. Lens' (CheckboxConfig t) (Dynamic t (Map String String)) Source
dropdown_value :: forall t k t k. Iso (Dropdown t k) (Dropdown t k) (Dynamic t k) (Dynamic t k) Source
dropdownConfig_setValue :: forall t k k. Lens (DropdownConfig t k) (DropdownConfig t k) (Event t k) (Event t k) Source
dropdownConfig_attributes :: forall t k. Lens' (DropdownConfig t k) (Dynamic t (Map String String)) Source
textInput_element :: forall t. Lens' (TextInput t) HTMLInputElement Source
textInputConfig_setValue :: forall t. Lens' (TextInputConfig t) (Event t String) Source
textInputConfig_inputType :: forall t. Lens' (TextInputConfig t) String Source
textInputConfig_initialValue :: forall t. Lens' (TextInputConfig t) String Source
textInputConfig_attributes :: forall t. Lens' (TextInputConfig t) (Dynamic t (Map String String)) Source
textArea_element :: forall t. Lens' (TextArea t) HTMLTextAreaElement Source
textAreaConfig_setValue :: forall t. Lens' (TextAreaConfig t) (Event t String) Source
textAreaConfig_initialValue :: forall t. Lens' (TextAreaConfig t) String Source
textAreaConfig_attributes :: forall t. Lens' (TextAreaConfig t) (Dynamic t (Map String String)) Source
class HasAttributes a where Source
attributes :: Lens' a (Attrs a) Source
class HasSetValue a where Source
(&) :: a -> (a -> b) -> b infixl 1
(.~) :: 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