haskell-halogen-core
Safe HaskellNone
LanguageGHC2021

Halogen.HTML

Synopsis

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 #

Relaxes the type of PlainHTML to make it compatible with all HTML.

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.

handler :: EventType -> (Event -> Maybe i) -> Prop i Source #

Create an event handler.

text :: Text -> HTML w i Source #

Constructs a text node HTML value.

newtype HTML w i Source #

Constructors

HTML 

Fields

Instances

Instances details
Bifunctor HTML Source # 
Instance details

Defined in Halogen.HTML.Core

Methods

bimap :: (a -> b) -> (c -> d) -> HTML a c -> HTML b d #

first :: (a -> b) -> HTML a c -> HTML b c #

second :: (b -> c) -> HTML a b -> HTML a c #

(Layout f, Default (LayoutConstraints f)) => AddLayout f w i (HTML w i) Source # 
Instance details

Defined in Halogen.HTML.Layout

Methods

(>>) :: HTML w i -> LayoutM f w i -> LayoutM f w i Source #

Layout f => AddLayout f w i (LayoutConstraints f, HTML w i) Source # 
Instance details

Defined in Halogen.HTML.Layout

Methods

(>>) :: (LayoutConstraints f, HTML w i) -> LayoutM f w i -> LayoutM f w i Source #

Functor (HTML w) Source # 
Instance details

Defined in Halogen.HTML.Core

Methods

fmap :: (a -> b) -> HTML w a -> HTML w b #

(<$) :: a -> HTML w b -> HTML w a #

class IsProp a where Source #

Methods

toPropValue :: a -> PropValue a Source #

Instances

Instances details
IsProp AutocompleteType Source # 
Instance details

Defined in Halogen.HTML.Core

IsProp ButtonType Source # 
Instance details

Defined in Halogen.HTML.Core

IsProp CrossOriginValue Source # 
Instance details

Defined in Halogen.HTML.Core

IsProp DirValue Source # 
Instance details

Defined in Halogen.HTML.Core

IsProp FormMethod Source # 
Instance details

Defined in Halogen.HTML.Core

IsProp InputAcceptType Source # 
Instance details

Defined in Halogen.HTML.Core

IsProp InputType Source # 
Instance details

Defined in Halogen.HTML.Core

IsProp KindValue Source # 
Instance details

Defined in Halogen.HTML.Core

IsProp MenuType Source # 
Instance details

Defined in Halogen.HTML.Core

IsProp MenuitemType Source # 
Instance details

Defined in Halogen.HTML.Core

IsProp OrderedListType Source # 
Instance details

Defined in Halogen.HTML.Core

IsProp PreloadValue Source # 
Instance details

Defined in Halogen.HTML.Core

IsProp ScopeValue Source # 
Instance details

Defined in Halogen.HTML.Core

IsProp StepValue Source # 
Instance details

Defined in Halogen.HTML.Core

IsProp WrapValue Source # 
Instance details

Defined in Halogen.HTML.Core

IsProp MediaType Source # 
Instance details

Defined in Halogen.HTML.Core

IsProp Text Source # 
Instance details

Defined in Halogen.HTML.Core

IsProp Bool Source # 
Instance details

Defined in Halogen.HTML.Core

IsProp Double Source # 
Instance details

Defined in Halogen.HTML.Core

Integral a => IsProp a Source # 
Instance details

Defined in Halogen.HTML.Core

Methods

toPropValue :: a -> PropValue a Source #

newtype ElemName Source #

Constructors

ElemName Text 

Instances

Instances details
IsString ElemName Source # 
Instance details

Defined in Halogen.VDom.Types

Show ElemName Source # 
Instance details

Defined in Halogen.VDom.Types

Eq ElemName Source # 
Instance details

Defined in Halogen.VDom.Types

Ord ElemName Source # 
Instance details

Defined in Halogen.VDom.Types

newtype Namespace Source #

Constructors

Namespace Text 

Instances

Instances details
IsString Namespace Source # 
Instance details

Defined in Halogen.VDom.Types

Show Namespace Source # 
Instance details

Defined in Halogen.VDom.Types

Eq Namespace Source # 
Instance details

Defined in Halogen.VDom.Types

Ord Namespace Source # 
Instance details

Defined in Halogen.VDom.Types

newtype AttrName Source #

Constructors

AttrName Text 

Instances

Instances details
IsString AttrName Source # 
Instance details

Defined in Web.HTML.Common

Show AttrName Source # 
Instance details

Defined in Web.HTML.Common

Eq AttrName Source # 
Instance details

Defined in Web.HTML.Common

Ord AttrName Source # 
Instance details

Defined in Web.HTML.Common

newtype ClassName Source #

Constructors

ClassName Text 

Instances

Instances details
IsString ClassName Source # 
Instance details

Defined in Web.HTML.Common

Show ClassName Source # 
Instance details

Defined in Web.HTML.Common

Eq ClassName Source # 
Instance details

Defined in Web.HTML.Common

Ord ClassName Source # 
Instance details

Defined in Web.HTML.Common

newtype PropName (value :: k) Source #

Constructors

PropName Text 

Instances

Instances details
IsString (PropName value) Source # 
Instance details

Defined in Web.HTML.Common

Methods

fromString :: String -> PropName value #

Show (PropName value) Source # 
Instance details

Defined in Web.HTML.Common

Methods

showsPrec :: Int -> PropName value -> ShowS #

show :: PropName value -> String #

showList :: [PropName value] -> ShowS #

Eq (PropName value) Source # 
Instance details

Defined in Web.HTML.Common

Methods

(==) :: PropName value -> PropName value -> Bool #

(/=) :: PropName value -> PropName value -> Bool #

Ord (PropName value) Source # 
Instance details

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 #

max :: PropName value -> PropName value -> PropName value #

min :: PropName value -> PropName value -> PropName value #

attr :: forall (r :: Row Type) msg. AttrName -> Text -> IProp r msg Source #

prop :: forall value (r :: Row Type) msg. IsProp value => PropName value -> value -> IProp r msg Source #

data IProp (r :: Row Type) msg Source #