Copyright | (c) Alexey Kuleshevich 2020 |
---|---|
License | BSD3 |
Maintainer | Alexey Kuleshevich <alexey@kuleshevi.ch> |
Stability | experimental |
Portability | non-portable |
Safe Haskell | None |
Language | Haskell2010 |
Synopsis
- type RW = RealWorld
- data RealWorld :: Type
- class MonadThrow m => MonadPrim s m | m -> s where
- class MonadUnliftPrim s m => MonadPrimBase s m where
- class MonadPrim s m => MonadUnliftPrim s m where
- withRunInPrimBase :: MonadPrimBase s n => ((forall a. m a -> n a) -> n b) -> m b
- prim_ :: MonadPrim s m => (State# s -> State# s) -> m ()
- primBase_ :: MonadPrimBase s m => m () -> State# s -> State# s
- runInPrimBase :: forall s m a b. MonadUnliftPrim s m => m a -> ((State# s -> (#State# s, a#)) -> State# s -> (#State# s, b#)) -> m b
- liftPrimIO :: MonadPrim RW m => IO a -> m a
- liftPrimST :: MonadPrim s m => ST s a -> m a
- liftPrimBase :: (MonadPrimBase s n, MonadPrim s m) => n a -> m a
- primBaseToIO :: MonadPrimBase RealWorld m => m a -> IO a
- primBaseToST :: MonadPrimBase s m => m a -> ST s a
- touch :: MonadPrim s m => a -> m ()
- seqPrim :: MonadPrim s m => a -> m a
- withAlivePrimBase :: (MonadPrimBase s n, MonadPrim s m) => a -> n b -> m b
- withAliveUnliftPrim :: MonadUnliftPrim s m => a -> m b -> m b
- showsType :: Typeable t => proxy t -> ShowS
- module Control.Monad
Documentation
RealWorld
is deeply magical. It is primitive, but it is not
unlifted (hence ptrArg
). We never manipulate values of type
RealWorld
; it's only used in the type system, to parameterise State#
.
Instances
MonadPrim RealWorld IO Source # | |
MonadUnliftPrim RealWorld IO Source # | |
Defined in Control.Prim.Monad.Internal withRunInPrimBase :: MonadPrimBase RealWorld n => ((forall a. IO a -> n a) -> n b) -> IO b Source # | |
MonadPrimBase RealWorld IO Source # | |
class MonadThrow m => MonadPrim s m | m -> s where Source #
Instances
MonadPrim RealWorld IO Source # | |
MonadPrim s m => MonadPrim s (MaybeT m) Source # | |
MonadPrim s (ST s) Source # | |
MonadPrim s m => MonadPrim s (SelectT r m) Source # | |
(Monoid w, MonadPrim s m) => MonadPrim s (AccumT w m) Source # | |
(Monoid w, MonadPrim s m) => MonadPrim s (WriterT w m) Source # | |
(Monoid w, MonadPrim s m) => MonadPrim s (WriterT w m) Source # | |
MonadPrim s m => MonadPrim s (StateT st m) Source # | |
MonadPrim s m => MonadPrim s (StateT st m) Source # | |
MonadPrim s m => MonadPrim s (IdentityT m) Source # | |
MonadPrim s m => MonadPrim s (ExceptT e m) Source # | |
MonadPrim s m => MonadPrim s (ReaderT r m) Source # | |
MonadPrim s m => MonadPrim s (ContT r m) Source # | |
(Monoid w, MonadPrim s m) => MonadPrim s (RWST r w st m) Source # | |
(Monoid w, MonadPrim s m) => MonadPrim s (RWST r w st m) Source # | |
class MonadUnliftPrim s m => MonadPrimBase s m where Source #
Instances
MonadPrimBase RealWorld IO Source # | |
MonadPrimBase s (ST s) Source # | |
MonadPrimBase s m => MonadPrimBase s (IdentityT m) Source # | |
class MonadPrim s m => MonadUnliftPrim s m where Source #
withRunInPrimBase :: MonadPrimBase s n => ((forall a. m a -> n a) -> n b) -> m b Source #
Instances
MonadUnliftPrim RealWorld IO Source # | |
Defined in Control.Prim.Monad.Internal withRunInPrimBase :: MonadPrimBase RealWorld n => ((forall a. IO a -> n a) -> n b) -> IO b Source # | |
MonadUnliftPrim s (ST s) Source # | |
Defined in Control.Prim.Monad.Internal withRunInPrimBase :: MonadPrimBase s n => ((forall a. ST s a -> n a) -> n b) -> ST s b Source # | |
MonadUnliftPrim s m => MonadUnliftPrim s (IdentityT m) Source # | |
Defined in Control.Prim.Monad.Internal withRunInPrimBase :: MonadPrimBase s n => ((forall a. IdentityT m a -> n a) -> n b) -> IdentityT m b Source # | |
MonadUnliftPrim s m => MonadUnliftPrim s (ReaderT r m) Source # | |
Defined in Control.Prim.Monad.Internal withRunInPrimBase :: MonadPrimBase s n => ((forall a. ReaderT r m a -> n a) -> n b) -> ReaderT r m b Source # |
prim_ :: MonadPrim s m => (State# s -> State# s) -> m () Source #
Construct a primitive action that does not return anything.
runInPrimBase :: forall s m a b. MonadUnliftPrim s m => m a -> ((State# s -> (#State# s, a#)) -> State# s -> (#State# s, b#)) -> m b Source #
liftPrimIO :: MonadPrim RW m => IO a -> m a Source #
Lift an IO
action to MonadPrim
with the RealWorld
state token. Type restricted
synonym for liftPrimBase
liftPrimST :: MonadPrim s m => ST s a -> m a Source #
Lift an ST
action to MonadPrim
with the same state token. Type restricted synonym
for liftPrimBase
liftPrimBase :: (MonadPrimBase s n, MonadPrim s m) => n a -> m a Source #
Lift an action from the MonadPrimBase
to another MonadPrim
with the same state
token.
primBaseToIO :: MonadPrimBase RealWorld m => m a -> IO a Source #
Restrict a MonadPrimBase
action that works with RealWorld
to IO
.
primBaseToST :: MonadPrimBase s m => m a -> ST s a Source #
Restrict a MonadPrimBase
action that works in ST
.
touch :: MonadPrim s m => a -> m () Source #
This is an action that ensures that the value is still available and garbage collector has not cleaned it up.
Make sure not to use it after some computation that doesn't return, like after
forever
for example, otherwise touch will simply be removed by ghc and bad things
will happen. If you have a case like that, make sure to use withAlivePrimBase
or
withAliveUnliftPrim
instead.
Since: 0.1.0
:: (MonadPrimBase s n, MonadPrim s m) | |
=> a | The value to preserve |
-> n b | Action to run in which the value will be preserved |
-> m b |
Similar to touch
. See withAlive#
for more info.
Since: 0.1.0
:: MonadUnliftPrim s m | |
=> a | The value to preserve |
-> m b | Action to run in which the value will be preserved |
-> m b |
Similar to touch
. See withAlive#
for more info.
Since: 0.1.0
showsType :: Typeable t => proxy t -> ShowS Source #
Helper function that converts a type into a string
Re-export
module Control.Monad