reflex-dom-core-0.8.1.3: Functional Reactive Web Apps with Reflex
Safe HaskellSafe-Inferred
LanguageHaskell98

Reflex.Dom.Widget.Input

Synopsis

Documentation

class HasValue a where Source #

Associated Types

type Value a :: Type 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) Source #

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) Source #

HasValue (TextArea t) Source # 
Instance details

Defined in Reflex.Dom.Widget.Input

Associated Types

type Value (TextArea t) Source #

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) Source #

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) Source #

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) Source #

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) Source #

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) Source #

Methods

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

data TextArea t 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) Source #

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

HasValue (TextInput t) Source # 
Instance details

Defined in Reflex.Dom.Widget.Input

Associated Types

type Value (TextInput t) Source #

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

data TextInputConfig t 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) Source #

HasAttributes (TextInputConfig t) Source # 
Instance details

Defined in Reflex.Dom.Widget.Input

Associated Types

type Attrs (TextInputConfig t) Source #

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

data RangeInput t Source #

Instances

Instances details
HasValue (RangeInput t) Source # 
Instance details

Defined in Reflex.Dom.Widget.Input

Associated Types

type Value (RangeInput t) Source #

type Value (RangeInput t) Source # 
Instance details

Defined in Reflex.Dom.Widget.Input

data TextAreaConfig t 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) Source #

HasAttributes (TextAreaConfig t) Source # 
Instance details

Defined in Reflex.Dom.Widget.Input

Associated Types

type Attrs (TextAreaConfig t) Source #

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 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) Source #

HasAttributes (CheckboxConfig t) Source # 
Instance details

Defined in Reflex.Dom.Widget.Input

Associated Types

type Attrs (CheckboxConfig t) Source #

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 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) Source #

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

newtype CheckboxViewEventResult en Source #

Deprecated: Use inputElement directly

data FileInput d t 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) Source #

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 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) Source #

type Attrs (FileInputConfig t) Source # 
Instance details

Defined in Reflex.Dom.Widget.Input

data Dropdown t k 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) Source #

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 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) Source #

HasAttributes (DropdownConfig t k2) Source # 
Instance details

Defined in Reflex.Dom.Widget.Input

Associated Types

type Attrs (DropdownConfig t k2) Source #

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

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 :: Reflex t => TextInput t -> Event t () Source #

Deprecated: Use 'keypress Enter' instead

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 :: forall t m. (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

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

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). Lens' (TextAreaConfig (t :: k)) (Dynamic t (Map Text Text)) Source #

dropdownConfig_attributes :: forall k (t :: k) k. Lens' (DropdownConfig (t :: k) k) (Dynamic t (Map Text Text)) Source #

checkboxConfig_attributes :: forall k (t :: k). Lens' (CheckboxConfig (t :: k)) (Dynamic t (Map Text Text)) Source #

fileInputConfig_attributes :: forall k (t :: k) k (t :: k). Iso (FileInputConfig (t :: k)) (FileInputConfig (t :: k)) (Dynamic t (Map Text Text)) (Dynamic t (Map Text Text)) Source #

textAreaConfig_setValue :: forall k (t :: k). Lens' (TextAreaConfig (t :: k)) (Event t Text) Source #

textInputConfig_setValue :: forall k (t :: k). Lens' (TextInputConfig (t :: k)) (Event t Text) Source #

rangeInputConfig_setValue :: forall k (t :: k). Lens' (RangeInputConfig (t :: k)) (Event t Float) Source #

dropdownConfig_setValue :: forall k (t :: k) k k. Lens (DropdownConfig (t :: k) k) (DropdownConfig (t :: k) k) (Event t k) (Event t k) Source #

checkboxConfig_setValue :: forall k (t :: k). Lens' (CheckboxConfig (t :: k)) (Event t Bool) Source #

textAreaConfig_initialValue :: forall k (t :: k). Lens' (TextAreaConfig (t :: k)) Text Source #

textArea_element :: forall k (t :: k). Lens' (TextArea (t :: k)) HTMLTextAreaElement Source #

textArea_hasFocus :: forall k (t :: k). Lens' (TextArea (t :: k)) (Dynamic t Bool) Source #

textArea_input :: forall k (t :: k). Lens' (TextArea (t :: k)) (Event t Text) Source #

textArea_keypress :: forall k (t :: k). Lens' (TextArea (t :: k)) (Event t Word) Source #

textArea_value :: forall k (t :: k). Lens' (TextArea (t :: k)) (Dynamic t Text) Source #

textInputConfig_inputType :: forall k (t :: k). Lens' (TextInputConfig (t :: k)) Text Source #

textInput_hasFocus :: forall k1 (t :: k1). Lens' (TextInput (t :: k1)) (Dynamic t Bool) Source #

textInput_input :: forall k1 (t :: k1). Lens' (TextInput (t :: k1)) (Event t Text) Source #

textInput_keydown :: forall k1 (t :: k1). Lens' (TextInput (t :: k1)) (Event t Word) Source #

textInput_keypress :: forall k1 (t :: k1). Lens' (TextInput (t :: k1)) (Event t Word) Source #

textInput_keyup :: forall k1 (t :: k1). Lens' (TextInput (t :: k1)) (Event t Word) Source #

textInput_value :: forall k1 (t :: k1). Lens' (TextInput (t :: k1)) (Dynamic t Text) Source #

rangeInput_element :: forall k (t :: k). Lens' (RangeInput (t :: k)) HTMLInputElement Source #

rangeInput_hasFocus :: forall k (t :: k). Lens' (RangeInput (t :: k)) (Dynamic t Bool) Source #

rangeInput_input :: forall k (t :: k). Lens' (RangeInput (t :: k)) (Event t Float) Source #

rangeInput_mouseup :: forall k (t :: k). Lens' (RangeInput (t :: k)) (Event t (Int, Int)) Source #

rangeInput_value :: forall k (t :: k). Lens' (RangeInput (t :: k)) (Dynamic t Float) Source #

fileInput_element :: forall k (d :: k) k (t :: k) k (d :: k). Lens (FileInput (d :: k) (t :: k)) (FileInput (d :: k) (t :: k)) (RawInputElement d) (RawInputElement d) Source #

fileInput_value :: forall k (d :: k) k (t :: k) k (t :: k). Lens (FileInput (d :: k) (t :: k)) (FileInput (d :: k) (t :: k)) (Dynamic t [File]) (Dynamic t [File]) Source #

dropdown_change :: forall k (t :: k) k. Lens' (Dropdown (t :: k) k) (Event t k) Source #

dropdown_value :: forall k (t :: k) k. Lens' (Dropdown (t :: k) k) (Dynamic t k) Source #

checkbox_change :: forall k (t :: k). Lens' (Checkbox (t :: k)) (Event t Bool) Source #

checkbox_value :: forall k (t :: k). Lens' (Checkbox (t :: k)) (Dynamic t Bool) 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 $.

>>> 5 & (+1) & show
"6"

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