Safe Haskell | None |
---|---|
Language | GHC2021 |
Halogen.Query.HalogenM
Synopsis
- newtype SubscriptionId = SubscriptionId Int
- newtype ForkId = ForkId Int
- data HalogenF state action (slots :: Row Type) output (m :: Type -> Type) a
- = 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)
- newtype HalogenM state action (slots :: Row Type) output (m :: Type -> Type) a = HalogenM (F (HalogenF state action slots output m) a)
- type HalogenIO state action (slots :: Row Type) output a = HalogenM state action slots output IO a
- newtype HalogenAp state action (slots :: Row Type) output (m :: Type -> Type) a = HalogenAp (Ap (HalogenM state action slots output m) a)
- raise :: forall state action (slots :: Row Type) output (m :: Type -> Type). Functor m => output -> HalogenM state action slots output m ()
- 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)
- 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)
- subscribe :: forall state action (slots :: Row Type) output (m :: Type -> Type). Functor m => Emitter IO action -> HalogenM state action slots output m SubscriptionId
- subscribe' :: forall state action (slots :: Row Type) output (m :: Type -> Type). Functor m => (SubscriptionId -> Emitter IO action) -> HalogenM state action slots output m ()
- unsubscribe :: forall state action (slots :: Row Type) output (m :: Type -> Type). Functor m => SubscriptionId -> HalogenM state action slots output m ()
- 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
- join :: forall state action (slots :: Row Type) output (m :: Type -> Type). Functor m => ForkId -> HalogenM state action slots output m ()
- kill :: forall state action (slots :: Row Type) output (m :: Type -> Type). Functor m => ForkId -> HalogenM state action slots output m ()
- getRef :: forall state action (slots :: Row Type) output (m :: Type -> Type). Functor m => RefLabel -> HalogenM state action slots output m (Maybe Element)
- imapState :: forall state state' action (slots :: Row Type) output (m :: Type -> Type) a. (state -> state') -> (state' -> state) -> HalogenM state action slots output m a -> HalogenM state' action slots output m a
- mapState :: forall state state' action (slots :: Row Type) output (m :: Type -> Type) a. (state' -> (state, state -> state')) -> HalogenM state action slots output m a -> HalogenM state' action slots output m a
- mapAction :: forall state action action' (slots :: Row Type) output (m :: Type -> Type) a. Functor m => (action -> action') -> HalogenM state action slots output m a -> HalogenM state action' slots output m a
- mapOutput :: forall state action (slots :: Row Type) output output' (m :: Type -> Type) a. (output -> output') -> HalogenM state action slots output m a -> HalogenM state action slots output' m a
- hoist :: forall state action (slots :: Row Type) output (m :: Type -> Type) (m' :: Type -> Type) a. Functor m' => (m ~> m') -> HalogenM state action slots output m a -> HalogenM state action slots output m' a
- mapHalogen :: forall state state' action action' (slots :: Row Type) output output' (m :: Type -> Type) (m' :: Type -> Type) a. (state' -> (state, state -> state')) -> (action -> action') -> (output -> output') -> (m ~> m') -> HalogenM state action slots output m a -> HalogenM state' action' slots output' m' a
- identityLens :: s -> (s, s -> s)
Documentation
newtype SubscriptionId Source #
Constructors
SubscriptionId Int |
Instances
Show SubscriptionId Source # | |
Defined in Halogen.Query.HalogenM Methods showsPrec :: Int -> SubscriptionId -> ShowS # show :: SubscriptionId -> String # showList :: [SubscriptionId] -> ShowS # | |
Eq SubscriptionId Source # | |
Defined in Halogen.Query.HalogenM Methods (==) :: SubscriptionId -> SubscriptionId -> Bool # (/=) :: SubscriptionId -> SubscriptionId -> Bool # | |
Ord SubscriptionId Source # | |
Defined in Halogen.Query.HalogenM Methods compare :: SubscriptionId -> SubscriptionId -> Ordering # (<) :: SubscriptionId -> SubscriptionId -> Bool # (<=) :: SubscriptionId -> SubscriptionId -> Bool # (>) :: SubscriptionId -> SubscriptionId -> Bool # (>=) :: SubscriptionId -> SubscriptionId -> Bool # max :: SubscriptionId -> SubscriptionId -> SubscriptionId # min :: SubscriptionId -> SubscriptionId -> SubscriptionId # |
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) |
newtype HalogenM state action (slots :: Row Type) output (m :: Type -> Type) a Source #
Instances
Functor m => MonadState state' (HalogenM state' action slots' output m) Source # | |||||
MonadTrans (HalogenM state' action slots' output) Source # | |||||
Defined in Halogen.Query.HalogenM | |||||
Applicative (HalogenM state action slots output m) Source # | |||||
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 # | |||||
Monad (HalogenM state action slots output m) Source # | |||||
Defined in Halogen.Query.HalogenM | |||||
MonadIO m => MonadIO (HalogenM state' action slots' output m) Source # | |||||
Defined in Halogen.Query.HalogenM | |||||
Functor m => MonadParallel (HalogenM state' action slots' output m) Source # | |||||
Defined in Halogen.Query.HalogenM Associated Types
| |||||
MonadUnliftIO m => MonadUnliftIO (HalogenM state' action slots' output m) Source # | |||||
Defined in Halogen.Query.HalogenM | |||||
type Parallel (HalogenM state' action slots' output m) Source # | |||||
Defined in Halogen.Query.HalogenM |
type HalogenIO state action (slots :: Row Type) output a = HalogenM state action slots output IO a Source #
newtype HalogenAp state action (slots :: Row Type) output (m :: Type -> Type) a Source #
Instances
Applicative (HalogenAp state action slots output m) Source # | |
Defined in Halogen.Query.HalogenM Methods pure :: a -> HalogenAp state action slots output m a # (<*>) :: HalogenAp state action slots output m (a -> b) -> HalogenAp state action slots output m a -> HalogenAp state action slots output m b # liftA2 :: (a -> b -> c) -> HalogenAp state action slots output m a -> HalogenAp state action slots output m b -> HalogenAp state action slots output m c # (*>) :: HalogenAp state action slots output m a -> HalogenAp state action slots output m b -> HalogenAp state action slots output m b # (<*) :: HalogenAp state action slots output m a -> HalogenAp state action slots output m b -> HalogenAp state action slots output m a # | |
Functor (HalogenAp state action slots output m) Source # | |
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.
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.
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.
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
| fork
ed 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.
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.
getRef :: forall state action (slots :: Row Type) output (m :: Type -> Type). Functor m => RefLabel -> HalogenM state action slots output m (Maybe Element) Source #
imapState :: forall state state' action (slots :: Row Type) output (m :: Type -> Type) a. (state -> state') -> (state' -> state) -> HalogenM state action slots output m a -> HalogenM state' action slots output m a Source #
mapState :: forall state state' action (slots :: Row Type) output (m :: Type -> Type) a. (state' -> (state, state -> state')) -> HalogenM state action slots output m a -> HalogenM state' action slots output m a Source #
mapAction :: forall state action action' (slots :: Row Type) output (m :: Type -> Type) a. Functor m => (action -> action') -> HalogenM state action slots output m a -> HalogenM state action' slots output m a Source #
mapOutput :: forall state action (slots :: Row Type) output output' (m :: Type -> Type) a. (output -> output') -> HalogenM state action slots output m a -> HalogenM state action slots output' m a Source #
hoist :: forall state action (slots :: Row Type) output (m :: Type -> Type) (m' :: Type -> Type) a. Functor m' => (m ~> m') -> HalogenM state action slots output m a -> HalogenM state action slots output m' a Source #
mapHalogen :: forall state state' action action' (slots :: Row Type) output output' (m :: Type -> Type) (m' :: Type -> Type) a. (state' -> (state, state -> state')) -> (action -> action') -> (output -> output') -> (m ~> m') -> HalogenM state action slots output m a -> HalogenM state' action' slots output' m' a Source #
identityLens :: s -> (s, s -> s) Source #