Safe Haskell | None |
---|---|
Language | GHC2021 |
Halogen.HTML
Synopsis
- type ComponentHTML action (slots :: Row Type) (m :: Type -> Type) = HTML (ComponentSlot slots m action) action
- type PlainHTML = HTML Void Void
- fromPlainHTML :: PlainHTML -> HTML w i
- mapHTMLAction :: forall a a' (slots :: Row Type) (m :: Type -> Type). (a -> a') -> ComponentHTML a slots m -> ComponentHTML a' slots m
- slot :: forall (label :: Symbol) -> forall (query :: Type -> Type) action input output (slots :: Row Type) (m :: Type -> Type) slot. (HasType label (Slot query output slot) slots, KnownSymbol label, Ord slot) => slot -> Component query input output m -> input -> (output -> action) -> ComponentHTML action slots m
- slot_ :: forall (label :: Symbol) -> forall (query :: Type -> Type) action input output (slots :: Row Type) (m :: Type -> Type) slot. (HasType label (Slot query output slot) slots, KnownSymbol label, Ord slot) => slot -> Component query input output m -> input -> ComponentHTML action slots m
- memoized :: forall a action (slots :: Row Type) (m :: Type -> Type). (a -> a -> Bool) -> (a -> ComponentHTML action slots m) -> a -> ComponentHTML action slots m
- lazy :: forall a action (slots :: Row Type) (m :: Type -> Type). (a -> ComponentHTML action slots m) -> a -> ComponentHTML action slots m
- handler :: EventType -> (Event -> Maybe i) -> Prop i
- text :: Text -> HTML w i
- newtype HTML w i = HTML {}
- class IsProp a where
- toPropValue :: a -> PropValue a
- newtype ElemName = ElemName Text
- newtype Namespace = Namespace Text
- newtype AttrName = AttrName Text
- newtype ClassName = ClassName Text
- newtype PropName (value :: k) = PropName Text
- module Halogen.HTML.Elements
- attr :: forall (r :: Row Type) msg. AttrName -> Text -> IProp r msg
- prop :: forall value (r :: Row Type) msg. IsProp value => PropName value -> value -> IProp r msg
- data IProp (r :: Row Type) msg
Documentation
type ComponentHTML action (slots :: Row Type) (m :: Type -> Type) = HTML (ComponentSlot slots m action) action Source #
A convenience synonym for the output type of a render
function for a
| component that renders HTML.
|
| - action
is the type of actions, events internal to the component that can
| be evaluated with the handleAction
function
| - slots
is the set of child component types that can be used in the HTML
| - m
is the monad used by the child component during evaluation
type PlainHTML = HTML Void Void Source #
A type useful for a chunk of HTML with no slot-embedding or query-raising.
|
| Often a polymorphic usage of HTML
is good enough for this, but sometimes
| it's useful to have a type like this (and accompanying coercion) when doing
| things like creating components that accept a chunk of HTML as part of
| their configuration.
fromPlainHTML :: PlainHTML -> HTML w i Source #
mapHTMLAction :: forall a a' (slots :: Row Type) (m :: Type -> Type). (a -> a') -> ComponentHTML a slots m -> ComponentHTML a' slots m Source #
slot :: forall (label :: Symbol) -> forall (query :: Type -> Type) action input output (slots :: Row Type) (m :: Type -> Type) slot. (HasType label (Slot query output slot) slots, KnownSymbol label, Ord slot) => slot -> Component query input output m -> input -> (output -> action) -> ComponentHTML action slots m Source #
Defines a slot for a child component. Takes: | - the slot address label | - the slot address index | - the component for the slot | - the input value to pass to the component | - a function mapping outputs from the component to a query in the parent
slot_ :: forall (label :: Symbol) -> forall (query :: Type -> Type) action input output (slots :: Row Type) (m :: Type -> Type) slot. (HasType label (Slot query output slot) slots, KnownSymbol label, Ord slot) => slot -> Component query input output m -> input -> ComponentHTML action slots m Source #
Defines a slot for a child component, ignoring its output.
|
| This variant may be used when the component produces output, but it is not
| needed in the current context, or instead of passing absurd
to slot
| when the output type is Void
.
|
| Takes:
| - the slot address label
| - the slot address index
| - the component for the slot
| - the input value to pass to the component
memoized :: forall a action (slots :: Row Type) (m :: Type -> Type). (a -> a -> Bool) -> (a -> ComponentHTML action slots m) -> a -> ComponentHTML action slots m Source #
Optimizes rendering of a subtree given an equality predicate. If an argument
| is deemed equivalent to the previous value, rendering and diffing will be
| skipped. You should not use this function fully saturated, but instead
| partially apply it for use within a Component's scope. For example, to skip
| rendering for equal states, just wrap your render
function.
|
| ```purescript
| myComponent = component
| { render: memoized eq render
| , ...
| }
| ```
lazy :: forall a action (slots :: Row Type) (m :: Type -> Type). (a -> ComponentHTML action slots m) -> a -> ComponentHTML action slots m Source #
Skips rendering for referentially equal arguments. You should not use this | function fully saturated, but instead partially apply it for use within a | Component's scope.
Methods
toPropValue :: a -> PropValue a Source #
Instances
Instances
IsString Namespace Source # | |
Defined in Halogen.VDom.Types Methods fromString :: String -> Namespace # | |
Show Namespace Source # | |
Eq Namespace Source # | |
Ord Namespace Source # | |
Instances
IsString ClassName Source # | |
Defined in Web.HTML.Common Methods fromString :: String -> ClassName # | |
Show ClassName Source # | |
Eq ClassName Source # | |
Ord ClassName Source # | |
newtype PropName (value :: k) Source #
Instances
IsString (PropName value) Source # | |
Defined in Web.HTML.Common Methods fromString :: String -> PropName value # | |
Show (PropName value) Source # | |
Eq (PropName value) Source # | |
Ord (PropName value) Source # | |
Defined in Web.HTML.Common Methods compare :: PropName value -> PropName value -> Ordering # (<) :: PropName value -> PropName value -> Bool # (<=) :: PropName value -> PropName value -> Bool # (>) :: PropName value -> PropName value -> Bool # (>=) :: PropName value -> PropName value -> Bool # |
module Halogen.HTML.Elements