haskell-halogen-core
Safe HaskellNone
LanguageGHC2021

Halogen.Component

Synopsis

Documentation

data ComponentSlotBox (slots :: Row Type) (m :: Type -> Type) msg Source #

Constructors

ComponentSlotBox 

Fields

Instances

Instances details
Functor (ComponentSlotBox slots' m) Source # 
Instance details

Defined in Halogen.Component

Methods

fmap :: (a -> b) -> ComponentSlotBox slots' m a -> ComponentSlotBox slots' m b #

(<$) :: a -> ComponentSlotBox slots' m b -> ComponentSlotBox slots' m a #

data ComponentSlot (slots :: Row Type) (m :: Type -> Type) msg Source #

Constructors

ComponentSlot (ComponentSlotBox slots m msg) 
ThunkSlot (Thunk (HTML (ComponentSlot slots m msg)) msg) 

Instances

Instances details
Functor (ComponentSlot slots' m) Source # 
Instance details

Defined in Halogen.Component

Methods

fmap :: (a -> b) -> ComponentSlot slots' m a -> ComponentSlot slots' m b #

(<$) :: a -> ComponentSlot slots' m b -> ComponentSlot slots' m a #

data ComponentSpec' state (query :: Type -> Type) action (slots :: Row Type) input output (m :: Type -> Type) (n :: Type -> Type) Source #

Constructors

ComponentSpec 

Fields

type ComponentSpec state (query :: Type -> Type) action (slots :: Row Type) input output (m :: Type -> Type) = ComponentSpec' state query action slots input output m (HalogenM state action slots output m) Source #

data Component (query :: Type -> Type) input output (m :: Type -> Type) Source #

Constructors

Component (ComponentSpec model query msg slots input output m) 

mkComponent :: forall state (query :: Type -> Type) action (slots :: Row Type) input output (m :: Type -> Type). ComponentSpec state query action slots input output m -> Component query input output m Source #

componentSlot :: forall (label :: Symbol) -> forall (query :: Type -> Type) input output (slots :: Row Type) (m :: Type -> Type) action slot. (HasType label (Slot query output slot) slots, KnownSymbol label, Ord slot) => slot -> Component query input output m -> input -> (output -> Maybe action) -> ComponentSlotBox slots m action Source #

Constructs a ComponentSlot | | 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

hoist :: forall (query :: Type -> Type) input output (m :: Type -> Type) (m' :: Type -> Type). Functor m' => (m ~> m') -> Component query input output m -> Component query input output m' Source #

Changes the Component's m type. A use case for this | might be to interpret some Free monad as IO so the component can be | used with runUI.

data EvalSpec state (query :: Type -> Type) action (slots :: Row Type) input output (m :: Type -> Type) Source #

The spec record that mkEval accepts to construct a component eval | function. | | It's not a requirement to use mkEval, and sometimes it's preferrable | to write a component eval function from scratch, but often mkEval is | more convenient for common cases. | | See below for more details about mkEval and defaultEval.

Constructors

EvalSpec 

Fields

defaultEval :: forall state (query :: Type -> Type) action (slots :: Row Type) input output (m :: Type -> Type). EvalSpec state query action slots input output m Source #

A default value for mkEval that will result in an eval that nothing at | all - all incoming actions and queries will be ignored, and no receiver, | initializer, or finalizer will be specified. | | Usually this will be used with record update syntax to override fields to | specify things as needed. If a component only needs to handle actions, | for instance, a usage might be something like this: | | ```purescript | H.mkComponent | { initialState | , render | , eval: H.mkEval (H.defaultEval { handleAction = ?handleAction }) | } | ```

mkEval :: forall state (query :: Type -> Type) action (slots :: Row Type) input output (m :: Type -> Type). EvalSpec state query action slots input output m -> HalogenQ query action input ~> HalogenM state action slots output m Source #

Accepts an EvalSpec to produce an eval function for a component. For | example: | | ```purescript | -- use defaultEval and override fields selectively | H.mkEval (H.defaultEval { handleAction = ?handleAction }) | | -- or specify all the fields in the EvalSpec | H.mkEval | { handleAction: ?handleAction | , handleQuery: ?handleQuery | , receive: ?receive | , initialize: ?initialize | , finalize: ?finalize | } | ```

hoistSlot :: forall (slots :: Row Type) (m :: Type -> Type) (m' :: Type -> Type) action. Functor m' => (m ~> m') -> ComponentSlot slots m action -> ComponentSlot slots m' action Source #

Changes the ComponentSlot's m type.