haskell-halogen-core
Safe HaskellNone
LanguageGHC2021

Halogen.IO.Driver.State

Documentation

data LifecycleHandlers (m :: Type -> Type) Source #

Constructors

LifecycleHandlers 

Fields

data DriverState (m :: Type -> Type) (r :: Type -> Type -> Row Type -> Type -> Type) s (f :: Type -> Type) act (ps :: Row Type) i o Source #

Constructors

DriverState 

data DriverStateRef (m :: Type -> Type) (r :: Type -> Type -> Row Type -> Type -> Type) (f :: Type -> Type) o Source #

Constructors

DriverStateRef (IORef (DriverState m r s f act ps i o)) 

data DriverStateX (m :: Type -> Type) (r :: Type -> Type -> Row Type -> Type -> Type) (f :: Type -> Type) o Source #

Constructors

DriverStateX (DriverState m r s f act ps i o) 

unDriverStateX :: forall (m :: Type -> Type) (r :: Type -> Type -> Row Type -> Type -> Type) (f :: Type -> Type) o a. (forall s act (ps :: Row Type) i. DriverState m r s f act ps i o -> a) -> DriverStateX m r f o -> a Source #

readDriverStateRef :: forall m (r :: Type -> Type -> Row Type -> Type -> Type) (f :: Type -> Type) o. MonadIO m => DriverStateRef m r f o -> m (DriverStateX m r f o) Source #

data RenderStateX (r :: Type -> Type -> Row Type -> Type -> Type) Source #

Constructors

RenderStateX (r s act ps o) 

renderStateX :: forall m r o (f :: Type -> Type). Functor m => (forall s act (ps :: Row Type). Maybe (r s act ps o) -> m (r s act ps o)) -> DriverStateX m r f o -> m (RenderStateX r) Source #

renderStateX_ :: forall m r o (f :: Type -> Type). Applicative m => (forall s act (ps :: Row Type). r s act ps o -> m ()) -> DriverStateX m r f o -> m () Source #

initDriverState :: forall m s (f :: Type -> Type) act (ps :: Row Type) i o (r :: Type -> Type -> Row Type -> Type -> Type). MonadIO m => ComponentSpec s f act ps i o m -> i -> (o -> m ()) -> IORef (LifecycleHandlers m) -> m (DriverState m r s f act ps i o) Source #