haskell-halogen-core
Safe HaskellNone
LanguageGHC2021

Halogen.Query

Description

Functions and types used to describe the HalogenF algebra used in a | component's eval function.

Synopsis

Documentation

type Tell (f :: Type -> Type) = () -> f () Source #

Type synonym for a "tell-style" query - queries that only cause effects, | but that cannot receive a return value. | | In a query algebra, a tell constructor carries the algebra's type variable | as its last argument. For example: | | ``` purescript | data Query a | = SomeTell a | | SomeOtherTell String a | | NotATell (Boolean -> a) | ``` | | Both SomeTell and SomeOtherTell carry a plain a as a value, whereas | NotATell has a as the result of a function so is considered to be a | "request" (see below).

mkTell :: Tell f -> f () Source #

Takes a data constructor of query algebra f and creates a tell query. | | For example: | | ```purescript | data Query a = Tick a | | sendTick :: forall o. H.HalogenSocket Query o IO -> IO (Maybe ()) | sendTick app = app.query (H.mkTell Tick) | ```

tell :: forall (label :: Symbol) -> forall state action output (m :: Type -> Type) (slots :: Row Type) (query :: Type -> Type) output' slot. (HasType label (Slot query output' slot) slots, Functor m, KnownSymbol label, Ord slot) => slot -> Tell query -> HalogenM state action slots output m () Source #

tellAll :: forall (label :: Symbol) -> forall state action output (m :: Type -> Type) (slots :: Row Type) (query :: Type -> Type) output' slot. (HasType label (Slot query output' slot) slots, Functor m, KnownSymbol label, Ord slot) => Tell query -> HalogenM state action slots output m () Source #

type Request (f :: Type -> Type) a = (a -> a) -> f a Source #

Type synonym for an "request-style" query - queries that can cause effects | as well as fetching some information from a component. | | In a query algebra, a request constructor carries the algebra's type | variable as the return value of a function as its last argument. For | example: | | ``` purescript | data Query a = SomeRequest (Boolean -> a) | ```

mkRequest :: Request f a -> f a Source #

Takes a data constructor of query algebra f and creates a request query. | | For example: | | ```purescript | data Query a = GetTickCount (Int -> a) | | getTickCount :: forall o. H.HalogenSocket Query o IO -> IO (Maybe Int) | getTickCount app = app.query (H.mkRequest GetTickCount) | ```

request :: forall (label :: Symbol) -> forall state action output (m :: Type -> Type) (slots :: Row Type) (query :: Type -> Type) output' slot a. (HasType label (Slot query output' slot) slots, Functor m, KnownSymbol label, Ord slot) => slot -> Request query a -> HalogenM state action slots output m (Maybe a) Source #

requestAll :: forall (label :: Symbol) -> forall state action output (m :: Type -> Type) (slots :: Row Type) (query :: Type -> Type) output' slot a. (HasType label (Slot query output' slot) slots, Functor m, KnownSymbol label, Ord slot) => Request query a -> HalogenM state action slots output m (Map slot a) Source #

getHTMLElementRef :: forall state action (slots :: Row Type) output (m :: Type -> Type). Functor m => RefLabel -> HalogenM state action slots output m (Maybe HTMLElement) Source #

Retrieves a HTMLElement value that is associated with a Ref in the | rendered output of a component. If there is no currently rendered value (or | it is not an HTMLElement) for the request will return Nothing.

newtype RefLabel Source #

Constructors

RefLabel Text 

fork :: forall state action (slots :: Row Type) output (m :: Type -> Type). Functor m => HalogenM state action slots output m () -> HalogenM state action slots output m ForkId Source #

Starts a HalogenM process running independent from the current eval | "thread". | | A commonly use case for fork is in component initializers where some | async action is started. Normally all interaction with the component will | be blocked until the initializer completes, but if the async action is | forked instead, the initializer can complete synchronously while the | async action continues. | | Some care needs to be taken when using a fork that can modify the | component state, as it's easy for the forked process to "clobber" the state | (overwrite some or all of it with an old value) by mistake. | | When a component is disposed of any active forks will automatically | be killed. New forks can be started during finalization but there will be | no means of killing them.

getRef :: forall state action (slots :: Row Type) output (m :: Type -> Type). Functor m => RefLabel -> HalogenM state action slots output m (Maybe Element) Source #

Retrieves an Element value that is associated with a Ref in the | rendered output of a component. If there is no currently rendered value for | the requested ref this will return Nothing.

join :: forall state action (slots :: Row Type) output (m :: Type -> Type). Functor m => ForkId -> HalogenM state action slots output m () Source #

Joins a forked process. Attempting to join a forked process that has | already ended will result in eval continuing immediately. Attempting | to join a forked process that has been killed will also terminate the | current eval.

kill :: forall state action (slots :: Row Type) output (m :: Type -> Type). Functor m => ForkId -> HalogenM state action slots output m () Source #

Kills a forked process if it is still running. Attempting to kill a forked | process that has already ended will have no effect.

query :: forall (label :: Symbol) -> forall state action output (m :: Type -> Type) (slots :: Row Type) (query :: Type -> Type) output' slot a. (HasType label (Slot query output' slot) slots, KnownSymbol label, Ord slot, Functor m) => slot -> query a -> HalogenM state action slots output m (Maybe a) Source #

Sends a query to a child of a component at the specified slot.

queryAll :: forall (label :: Symbol) -> forall state action output (m :: Type -> Type) (slots :: Row Type) (query :: Type -> Type) output' slot a. (HasType label (Slot query output' slot) slots, KnownSymbol label, Ord slot, Functor m) => query a -> HalogenM state action slots output m (Map slot a) Source #

Sends a query to all children of a component at a given slot label.

raise :: forall state action (slots :: Row Type) output (m :: Type -> Type). Functor m => output -> HalogenM state action slots output m () Source #

Raises an output message for the component.

subscribe :: forall state action (slots :: Row Type) output (m :: Type -> Type). Functor m => Emitter IO action -> HalogenM state action slots output m SubscriptionId Source #

Subscribes a component to an Emitter. | | When a component is disposed of any active subscriptions will automatically | be stopped and no further subscriptions will be possible during | finalization.

subscribe' :: forall state action (slots :: Row Type) output (m :: Type -> Type). Functor m => (SubscriptionId -> Emitter IO action) -> HalogenM state action slots output m () Source #

An alternative to subscribe, intended for subscriptions that unsubscribe | themselves. Instead of returning the SubscriptionId from subscribe', it | is passed into an Emitter constructor. This allows emitted queries | to include the SubscriptionId, rather than storing it in the state of the | component. | | When a component is disposed of any active subscriptions will automatically | be stopped and no further subscriptions will be possible during | finalization.

unsubscribe :: forall state action (slots :: Row Type) output (m :: Type -> Type). Functor m => SubscriptionId -> HalogenM state action slots output m () Source #

Unsubscribes a component from a subscription. If the subscription associated | with the ID has already ended this will have no effect.

data ForkId Source #

Instances

Instances details
Show ForkId Source # 
Instance details

Defined in Halogen.Query.HalogenM

Eq ForkId Source # 
Instance details

Defined in Halogen.Query.HalogenM

Methods

(==) :: ForkId -> ForkId -> Bool #

(/=) :: ForkId -> ForkId -> Bool #

Ord ForkId Source # 
Instance details

Defined in Halogen.Query.HalogenM

data HalogenF state action (slots :: Row Type) output (m :: Type -> Type) a Source #

Constructors

State (state -> (a, state)) 
Subscribe (SubscriptionId -> Emitter IO action) (SubscriptionId -> a) 
Unsubscribe SubscriptionId a 
Lift (m a) 
Unlift (UnliftIO (HalogenM state action slots output m) -> IO a) 
ChildQuery (ChildQuery slots a) 
Raise output a 
Par (HalogenAp state action slots output m a) 
Fork (HalogenM state action slots output m ()) (ForkId -> a) 
Join ForkId a 
Kill ForkId a 
GetRef RefLabel (Maybe Element -> a) 

Instances

Instances details
Functor m => Functor (HalogenF state action slots output m) Source # 
Instance details

Defined in Halogen.Query.HalogenM

Methods

fmap :: (a -> b) -> HalogenF state action slots output m a -> HalogenF state action slots output m b #

(<$) :: a -> HalogenF state action slots output m b -> HalogenF state action slots output m a #

newtype HalogenM state action (slots :: Row Type) output (m :: Type -> Type) a Source #

Constructors

HalogenM (F (HalogenF state action slots output m) a) 

Instances

Instances details
Functor m => MonadState state' (HalogenM state' action slots' output m) Source # 
Instance details

Defined in Halogen.Query.HalogenM

Methods

get :: HalogenM state' action slots' output m state' #

put :: state' -> HalogenM state' action slots' output m () #

state :: (state' -> (a, state')) -> HalogenM state' action slots' output m a #

MonadTrans (HalogenM state' action slots' output) Source # 
Instance details

Defined in Halogen.Query.HalogenM

Methods

lift :: Monad m => m a -> HalogenM state' action slots' output m a #

Applicative (HalogenM state action slots output m) Source # 
Instance details

Defined in Halogen.Query.HalogenM

Methods

pure :: a -> HalogenM state action slots output m a #

(<*>) :: HalogenM state action slots output m (a -> b) -> HalogenM state action slots output m a -> HalogenM state action slots output m b #

liftA2 :: (a -> b -> c) -> HalogenM state action slots output m a -> HalogenM state action slots output m b -> HalogenM state action slots output m c #

(*>) :: HalogenM state action slots output m a -> HalogenM state action slots output m b -> HalogenM state action slots output m b #

(<*) :: HalogenM state action slots output m a -> HalogenM state action slots output m b -> HalogenM state action slots output m a #

Functor (HalogenM state action slots output m) Source # 
Instance details

Defined in Halogen.Query.HalogenM

Methods

fmap :: (a -> b) -> HalogenM state action slots output m a -> HalogenM state action slots output m b #

(<$) :: a -> HalogenM state action slots output m b -> HalogenM state action slots output m a #

Monad (HalogenM state action slots output m) Source # 
Instance details

Defined in Halogen.Query.HalogenM

Methods

(>>=) :: HalogenM state action slots output m a -> (a -> HalogenM state action slots output m b) -> HalogenM state action slots output m b #

(>>) :: HalogenM state action slots output m a -> HalogenM state action slots output m b -> HalogenM state action slots output m b #

return :: a -> HalogenM state action slots output m a #

MonadIO m => MonadIO (HalogenM state' action slots' output m) Source # 
Instance details

Defined in Halogen.Query.HalogenM

Methods

liftIO :: IO a -> HalogenM state' action slots' output m a #

Functor m => MonadParallel (HalogenM state' action slots' output m) Source # 
Instance details

Defined in Halogen.Query.HalogenM

Associated Types

type Parallel (HalogenM state' action slots' output m) 
Instance details

Defined in Halogen.Query.HalogenM

type Parallel (HalogenM state' action slots' output m) = HalogenAp state' action slots' output m

Methods

parallel :: HalogenM state' action slots' output m a -> Parallel (HalogenM state' action slots' output m) a Source #

sequential :: Parallel (HalogenM state' action slots' output m) a -> HalogenM state' action slots' output m a Source #

MonadUnliftIO m => MonadUnliftIO (HalogenM state' action slots' output m) Source # 
Instance details

Defined in Halogen.Query.HalogenM

Methods

withRunInIO :: ((forall a. HalogenM state' action slots' output m a -> IO a) -> IO b) -> HalogenM state' action slots' output m b #

type Parallel (HalogenM state' action slots' output m) Source # 
Instance details

Defined in Halogen.Query.HalogenM

type Parallel (HalogenM state' action slots' output m) = HalogenAp state' action slots' output m