reflex-dom-core-0.8.1.4: Functional Reactive Web Apps with Reflex
Safe HaskellNone
LanguageHaskell98

Reflex.Dom.Widget.Input

Synopsis

Documentation

class HasValue a where Source #

Associated Types

type Value a Source #

Methods

value :: a -> Value a Source #

Instances

Instances details
HasValue (Checkbox t) Source # 
Instance details

Defined in Reflex.Dom.Widget.Input

Associated Types

type Value (Checkbox t) 
Instance details

Defined in Reflex.Dom.Widget.Input

type Value (Checkbox t) = Dynamic t Bool

Methods

value :: Checkbox t -> Value (Checkbox t) Source #

HasValue (RangeInput t) Source # 
Instance details

Defined in Reflex.Dom.Widget.Input

Associated Types

type Value (RangeInput t) 
Instance details

Defined in Reflex.Dom.Widget.Input

HasValue (TextArea t) Source # 
Instance details

Defined in Reflex.Dom.Widget.Input

Associated Types

type Value (TextArea t) 
Instance details

Defined in Reflex.Dom.Widget.Input

type Value (TextArea t) = Dynamic t Text

Methods

value :: TextArea t -> Value (TextArea t) Source #

HasValue (TextInput t) Source # 
Instance details

Defined in Reflex.Dom.Widget.Input

Associated Types

type Value (TextInput t) 
Instance details

Defined in Reflex.Dom.Widget.Input

Methods

value :: TextInput t -> Value (TextInput t) Source #

HasValue (Dropdown t k2) Source # 
Instance details

Defined in Reflex.Dom.Widget.Input

Associated Types

type Value (Dropdown t k2) 
Instance details

Defined in Reflex.Dom.Widget.Input

type Value (Dropdown t k2) = Dynamic t k2

Methods

value :: Dropdown t k2 -> Value (Dropdown t k2) Source #

HasValue (FileInput d t) Source # 
Instance details

Defined in Reflex.Dom.Widget.Input

Associated Types

type Value (FileInput d t) 
Instance details

Defined in Reflex.Dom.Widget.Input

type Value (FileInput d t) = Dynamic t [File]

Methods

value :: FileInput d t -> Value (FileInput d t) Source #

HasValue (InputElement er d t) Source # 
Instance details

Defined in Reflex.Dom.Widget.Input

Associated Types

type Value (InputElement er d t) 
Instance details

Defined in Reflex.Dom.Widget.Input

type Value (InputElement er d t) = Dynamic t Text

Methods

value :: InputElement er d t -> Value (InputElement er d t) Source #

HasValue (TextAreaElement er d t) Source # 
Instance details

Defined in Reflex.Dom.Widget.Input

Associated Types

type Value (TextAreaElement er d t) 
Instance details

Defined in Reflex.Dom.Widget.Input

type Value (TextAreaElement er d t) = Dynamic t Text

Methods

value :: TextAreaElement er d t -> Value (TextAreaElement er d t) Source #

type family Value a Source #

Instances

Instances details
type Value (Checkbox t) Source # 
Instance details

Defined in Reflex.Dom.Widget.Input

type Value (Checkbox t) = Dynamic t Bool
type Value (RangeInput t) Source # 
Instance details

Defined in Reflex.Dom.Widget.Input

type Value (TextArea t) Source # 
Instance details

Defined in Reflex.Dom.Widget.Input

type Value (TextArea t) = Dynamic t Text
type Value (TextInput t) Source # 
Instance details

Defined in Reflex.Dom.Widget.Input

type Value (Dropdown t k2) Source # 
Instance details

Defined in Reflex.Dom.Widget.Input

type Value (Dropdown t k2) = Dynamic t k2
type Value (FileInput d t) Source # 
Instance details

Defined in Reflex.Dom.Widget.Input

type Value (FileInput d t) = Dynamic t [File]
type Value (InputElement er d t) Source # 
Instance details

Defined in Reflex.Dom.Widget.Input

type Value (InputElement er d t) = Dynamic t Text
type Value (TextAreaElement er d t) Source # 
Instance details

Defined in Reflex.Dom.Widget.Input

type Value (TextAreaElement er d t) = Dynamic t Text

data TextArea (t :: k) Source #

Deprecated: Use textAreaElement directly

Instances

Instances details
HasValue (TextArea t) Source # 
Instance details

Defined in Reflex.Dom.Widget.Input

Associated Types

type Value (TextArea t) 
Instance details

Defined in Reflex.Dom.Widget.Input

type Value (TextArea t) = Dynamic t Text

Methods

value :: TextArea t -> Value (TextArea t) Source #

type Value (TextArea t) Source # 
Instance details

Defined in Reflex.Dom.Widget.Input

type Value (TextArea t) = Dynamic t Text

data TextInput (t :: k1) Source #

Deprecated: Use inputElement directly

Instances

Instances details
Reflex t => HasDomEvent (t :: k1) (TextInput t) en Source # 
Instance details

Defined in Reflex.Dom.Widget.Input

Associated Types

type DomEventType (TextInput t) en 
Instance details

Defined in Reflex.Dom.Widget.Input

HasValue (TextInput t) Source # 
Instance details

Defined in Reflex.Dom.Widget.Input

Associated Types

type Value (TextInput t) 
Instance details

Defined in Reflex.Dom.Widget.Input

Methods

value :: TextInput t -> Value (TextInput t) Source #

type Value (TextInput t) Source # 
Instance details

Defined in Reflex.Dom.Widget.Input

type DomEventType (TextInput t) en Source # 
Instance details

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

Instances

Instances details
Reflex t => Default (TextInputConfig t) Source # 
Instance details

Defined in Reflex.Dom.Widget.Input

Methods

def :: TextInputConfig t #

HasSetValue (TextInputConfig t) Source # 
Instance details

Defined in Reflex.Dom.Widget.Input

Associated Types

type SetValue (TextInputConfig t) 
Instance details

Defined in Reflex.Dom.Widget.Input

HasAttributes (TextInputConfig t) Source # 
Instance details

Defined in Reflex.Dom.Widget.Input

Associated Types

type Attrs (TextInputConfig t) 
Instance details

Defined in Reflex.Dom.Widget.Input

type SetValue (TextInputConfig t) Source # 
Instance details

Defined in Reflex.Dom.Widget.Input

type Attrs (TextInputConfig t) Source # 
Instance details

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 #

Instances

Instances details
Reflex t => Default (RangeInputConfig t) Source # 
Instance details

Defined in Reflex.Dom.Widget.Input

Methods

def :: RangeInputConfig t #

HasSetValue (RangeInputConfig t) Source # 
Instance details

Defined in Reflex.Dom.Widget.Input

Associated Types

type SetValue (RangeInputConfig t) 
Instance details

Defined in Reflex.Dom.Widget.Input

HasAttributes (RangeInputConfig t) Source # 
Instance details

Defined in Reflex.Dom.Widget.Input

Associated Types

type Attrs (RangeInputConfig t) 
Instance details

Defined in Reflex.Dom.Widget.Input

type SetValue (RangeInputConfig t) Source # 
Instance details

Defined in Reflex.Dom.Widget.Input

type Attrs (RangeInputConfig t) Source # 
Instance details

Defined in Reflex.Dom.Widget.Input

data RangeInput (t :: k) Source #

Instances

Instances details
HasValue (RangeInput t) Source # 
Instance details

Defined in Reflex.Dom.Widget.Input

Associated Types

type Value (RangeInput t) 
Instance details

Defined in Reflex.Dom.Widget.Input

type Value (RangeInput t) Source # 
Instance details

Defined in Reflex.Dom.Widget.Input

data TextAreaConfig (t :: k) Source #

Deprecated: Use textAreaElement directly

Instances

Instances details
Reflex t => Default (TextAreaConfig t) Source # 
Instance details

Defined in Reflex.Dom.Widget.Input

Methods

def :: TextAreaConfig t #

HasSetValue (TextAreaConfig t) Source # 
Instance details

Defined in Reflex.Dom.Widget.Input

Associated Types

type SetValue (TextAreaConfig t) 
Instance details

Defined in Reflex.Dom.Widget.Input

HasAttributes (TextAreaConfig t) Source # 
Instance details

Defined in Reflex.Dom.Widget.Input

Associated Types

type Attrs (TextAreaConfig t) 
Instance details

Defined in Reflex.Dom.Widget.Input

type SetValue (TextAreaConfig t) Source # 
Instance details

Defined in Reflex.Dom.Widget.Input

type Attrs (TextAreaConfig t) Source # 
Instance details

Defined in Reflex.Dom.Widget.Input

data CheckboxConfig (t :: k) Source #

Deprecated: Use inputElement directly

Instances

Instances details
Reflex t => Default (CheckboxConfig t) Source # 
Instance details

Defined in Reflex.Dom.Widget.Input

Methods

def :: CheckboxConfig t #

HasSetValue (CheckboxConfig t) Source # 
Instance details

Defined in Reflex.Dom.Widget.Input

Associated Types

type SetValue (CheckboxConfig t) 
Instance details

Defined in Reflex.Dom.Widget.Input

HasAttributes (CheckboxConfig t) Source # 
Instance details

Defined in Reflex.Dom.Widget.Input

Associated Types

type Attrs (CheckboxConfig t) 
Instance details

Defined in Reflex.Dom.Widget.Input

type SetValue (CheckboxConfig t) Source # 
Instance details

Defined in Reflex.Dom.Widget.Input

type Attrs (CheckboxConfig t) Source # 
Instance details

Defined in Reflex.Dom.Widget.Input

data Checkbox (t :: k) Source #

Deprecated: Use inputElement directly

Constructors

Checkbox

Deprecated: Use inputElement directly

Instances

Instances details
HasValue (Checkbox t) Source # 
Instance details

Defined in Reflex.Dom.Widget.Input

Associated Types

type Value (Checkbox t) 
Instance details

Defined in Reflex.Dom.Widget.Input

type Value (Checkbox t) = Dynamic t Bool

Methods

value :: Checkbox t -> Value (Checkbox t) Source #

type Value (Checkbox t) Source # 
Instance details

Defined in Reflex.Dom.Widget.Input

type Value (Checkbox t) = Dynamic t Bool

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

newtype CheckboxViewEventResult (en :: EventTag) Source #

Deprecated: Use inputElement directly

data FileInput (d :: k) (t :: k1) Source #

Deprecated: Use inputElement directly

Constructors

FileInput

Deprecated: Use inputElement directly

Instances

Instances details
HasValue (FileInput d t) Source # 
Instance details

Defined in Reflex.Dom.Widget.Input

Associated Types

type Value (FileInput d t) 
Instance details

Defined in Reflex.Dom.Widget.Input

type Value (FileInput d t) = Dynamic t [File]

Methods

value :: FileInput d t -> Value (FileInput d t) Source #

type Value (FileInput d t) Source # 
Instance details

Defined in Reflex.Dom.Widget.Input

type Value (FileInput d t) = Dynamic t [File]

newtype FileInputConfig (t :: k) Source #

Deprecated: Use inputElement directly

Constructors

FileInputConfig

Deprecated: Use inputElement directly

Instances

Instances details
Reflex t => Default (FileInputConfig t) Source # 
Instance details

Defined in Reflex.Dom.Widget.Input

Methods

def :: FileInputConfig t #

HasAttributes (FileInputConfig t) Source # 
Instance details

Defined in Reflex.Dom.Widget.Input

Associated Types

type Attrs (FileInputConfig t) 
Instance details

Defined in Reflex.Dom.Widget.Input

type Attrs (FileInputConfig t) Source # 
Instance details

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 

Instances

Instances details
HasValue (Dropdown t k2) Source # 
Instance details

Defined in Reflex.Dom.Widget.Input

Associated Types

type Value (Dropdown t k2) 
Instance details

Defined in Reflex.Dom.Widget.Input

type Value (Dropdown t k2) = Dynamic t k2

Methods

value :: Dropdown t k2 -> Value (Dropdown t k2) Source #

type Value (Dropdown t k2) Source # 
Instance details

Defined in Reflex.Dom.Widget.Input

type Value (Dropdown t k2) = Dynamic t k2

data DropdownConfig (t :: k) k1 Source #

Instances

Instances details
Reflex t => Default (DropdownConfig t k2) Source # 
Instance details

Defined in Reflex.Dom.Widget.Input

Methods

def :: DropdownConfig t k2 #

HasSetValue (DropdownConfig t k2) Source # 
Instance details

Defined in Reflex.Dom.Widget.Input

Associated Types

type SetValue (DropdownConfig t k2) 
Instance details

Defined in Reflex.Dom.Widget.Input

type SetValue (DropdownConfig t k2) = Event t k2
HasAttributes (DropdownConfig t k2) Source # 
Instance details

Defined in Reflex.Dom.Widget.Input

Associated Types

type Attrs (DropdownConfig t k2) 
Instance details

Defined in Reflex.Dom.Widget.Input

type SetValue (DropdownConfig t k2) Source # 
Instance details

Defined in Reflex.Dom.Widget.Input

type SetValue (DropdownConfig t k2) = Event t k2
type Attrs (DropdownConfig t k2) Source # 
Instance details

Defined in Reflex.Dom.Widget.Input

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_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 #

def :: Default a => a #

The default value for this type.

(&) :: 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 flip id, where 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

Expand
>>> 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