| Safe Haskell | Safe-Inferred | 
|---|---|
| Language | Haskell2010 | 
IncipitCore
Description
This is the central module on which to build upon when constructing Preludes for Polysemy libraries. It reexports most core effects.
Synopsis
- module Incipit.Exception
- module IncipitBase
- embedToFinal :: forall (m :: Type -> Type) (r :: EffectRow) a. (Member (Final m) r, Functor m) => Sem (Embed m ': r) a -> Sem r a
- runFinal :: Monad m => Sem '[Final m] a -> m a
- embedFinal :: forall m (r :: EffectRow) a. (Member (Final m) r, Functor m) => m a -> Sem r a
- data Final (m :: Type -> Type) (z :: Type -> Type) a
- transform :: forall e1 e2 (r :: EffectRow) a. Member e2 r => (forall (rInitial :: EffectRow) x. e1 (Sem rInitial) x -> e2 (Sem rInitial) x) -> Sem (e1 ': r) a -> Sem r a
- rewrite :: forall e1 e2 (r :: [Effect]) a. (forall (rInitial :: EffectRow) x. e1 (Sem rInitial) x -> e2 (Sem rInitial) x) -> Sem (e1 ': r) a -> Sem (e2 ': r) a
- interceptH :: forall e (r :: EffectRow) a. Member e r => (forall x (rInitial :: EffectRow). e (Sem rInitial) x -> Tactical e (Sem rInitial) r x) -> Sem r a -> Sem r a
- intercept :: forall e (r :: EffectRow) a. (Member e r, FirstOrder e "intercept") => (forall x (rInitial :: EffectRow). e (Sem rInitial) x -> Sem r x) -> Sem r a -> Sem r a
- reinterpret3 :: forall e1 (e2 :: Effect) (e3 :: Effect) (e4 :: Effect) (r :: [Effect]) a. FirstOrder e1 "reinterpret3" => (forall (rInitial :: EffectRow) x. e1 (Sem rInitial) x -> Sem (e2 ': (e3 ': (e4 ': r))) x) -> Sem (e1 ': r) a -> Sem (e2 ': (e3 ': (e4 ': r))) a
- reinterpret3H :: forall e1 (e2 :: Effect) (e3 :: Effect) (e4 :: Effect) (r :: [Effect]) a. (forall (rInitial :: EffectRow) x. e1 (Sem rInitial) x -> Tactical e1 (Sem rInitial) (e2 ': (e3 ': (e4 ': r))) x) -> Sem (e1 ': r) a -> Sem (e2 ': (e3 ': (e4 ': r))) a
- reinterpret2 :: forall e1 (e2 :: Effect) (e3 :: Effect) (r :: [Effect]) a. FirstOrder e1 "reinterpret2" => (forall (rInitial :: EffectRow) x. e1 (Sem rInitial) x -> Sem (e2 ': (e3 ': r)) x) -> Sem (e1 ': r) a -> Sem (e2 ': (e3 ': r)) a
- reinterpret2H :: forall e1 (e2 :: Effect) (e3 :: Effect) (r :: [Effect]) a. (forall (rInitial :: EffectRow) x. e1 (Sem rInitial) x -> Tactical e1 (Sem rInitial) (e2 ': (e3 ': r)) x) -> Sem (e1 ': r) a -> Sem (e2 ': (e3 ': r)) a
- reinterpret :: forall e1 (e2 :: Effect) (r :: [Effect]) a. FirstOrder e1 "reinterpret" => (forall (rInitial :: EffectRow) x. e1 (Sem rInitial) x -> Sem (e2 ': r) x) -> Sem (e1 ': r) a -> Sem (e2 ': r) a
- reinterpretH :: forall e1 (e2 :: Effect) (r :: [Effect]) a. (forall (rInitial :: EffectRow) x. e1 (Sem rInitial) x -> Tactical e1 (Sem rInitial) (e2 ': r) x) -> Sem (e1 ': r) a -> Sem (e2 ': r) a
- interpretH :: forall e (r :: [Effect]) a. (forall (rInitial :: EffectRow) x. e (Sem rInitial) x -> Tactical e (Sem rInitial) r x) -> Sem (e ': r) a -> Sem r a
- interpret :: forall e (r :: [Effect]) a. FirstOrder e "interpret" => (forall (rInitial :: EffectRow) x. e (Sem rInitial) x -> Sem r x) -> Sem (e ': r) a -> Sem r a
- makeSem_ :: Name -> Q [Dec]
- makeSem :: Name -> Q [Dec]
- bindTSimple :: forall m f (r :: [Effect]) (e :: Effect) a b. (a -> m b) -> f a -> Sem (WithTactics e f m r) (f b)
- bindT :: forall a m b (e :: Effect) f (r :: [Effect]). (a -> m b) -> Sem (WithTactics e f m r) (f a -> Sem (e ': r) (f b))
- runTSimple :: forall m a (e :: Effect) (r :: [Effect]). m a -> Tactical e m r a
- runT :: forall m a (e :: Effect) f (r :: [Effect]). m a -> Sem (WithTactics e f m r) (Sem (e ': r) (f a))
- pureT :: forall f a (e :: Effect) (m :: Type -> Type) (r :: [Effect]). Functor f => a -> Sem (WithTactics e f m r) (f a)
- getInspectorT :: forall (e :: Effect) (f :: Type -> TYPE LiftedRep) (m :: Type -> Type) (r :: [Effect]). Sem (WithTactics e f m r) (Inspector f)
- getInitialStateT :: forall f (m :: Type -> Type) (r :: [Effect]) (e :: Effect). Sem (WithTactics e f m r) (f ())
- type Tactical (e :: Effect) (m :: Type -> Type) (r :: [Effect]) x = forall (f :: Type -> Type). Functor f => Sem (WithTactics e f m r) (f x)
- type WithTactics (e :: Effect) (f :: Type -> TYPE LiftedRep) (m :: Type -> Type) (r :: [Effect]) = (Tactics f m (e ': r) :: (Type -> Type) -> TYPE LiftedRep -> Type) ': r
- newtype Inspector (f :: Type -> Type) = Inspector {}
- runM :: Monad m => Sem '[Embed m] a -> m a
- embed :: forall m (r :: EffectRow) a. Member (Embed m) r => m a -> Sem r a
- send :: forall e (r :: EffectRow) a. Member e r => e (Sem r) a -> Sem r a
- insertAt :: forall (index :: Nat) (inserted :: [Effect]) (head :: [Effect]) (oldTail :: [Effect]) (tail :: [Effect]) (old :: [Effect]) (full :: [Effect]) a. (ListOfLength index head, WhenStuck index (InsertAtUnprovidedIndex :: Constraint), old ~ Append head oldTail, tail ~ Append inserted oldTail, full ~ Append head tail, InsertAtIndex index head tail oldTail full inserted) => Sem old a -> Sem full a
- subsume :: forall (e :: Effect) (r :: EffectRow) a. Member e r => Sem (e ': r) a -> Sem r a
- subsume_ :: forall (r :: EffectRow) (r' :: EffectRow) a. Subsume r r' => Sem r a -> Sem r' a
- raise3Under :: forall (e4 :: Effect) (e1 :: Effect) (e2 :: Effect) (e3 :: Effect) (r :: [Effect]) a. Sem (e1 ': (e2 ': (e3 ': r))) a -> Sem (e1 ': (e2 ': (e3 ': (e4 ': r)))) a
- raise2Under :: forall (e3 :: Effect) (e1 :: Effect) (e2 :: Effect) (r :: [Effect]) a. Sem (e1 ': (e2 ': r)) a -> Sem (e1 ': (e2 ': (e3 ': r))) a
- raiseUnder3 :: forall (e2 :: Effect) (e3 :: Effect) (e4 :: Effect) (e1 :: Effect) (r :: [Effect]) a. Sem (e1 ': r) a -> Sem (e1 ': (e2 ': (e3 ': (e4 ': r)))) a
- raiseUnder2 :: forall (e2 :: Effect) (e3 :: Effect) (e1 :: Effect) (r :: [Effect]) a. Sem (e1 ': r) a -> Sem (e1 ': (e2 ': (e3 ': r))) a
- raiseUnder :: forall (e2 :: Effect) (e1 :: Effect) (r :: [Effect]) a. Sem (e1 ': r) a -> Sem (e1 ': (e2 ': r)) a
- raise :: forall (e :: Effect) (r :: EffectRow) a. Sem r a -> Sem (e ': r) a
- raise_ :: forall (r :: EffectRow) (r' :: EffectRow) a. Raise r r' => Sem r a -> Sem r' a
- type family Members (es :: [Effect]) (r :: EffectRow) where ...
- type InterpreterFor (e :: Effect) (r :: [Effect]) = forall a. Sem (e ': r) a -> Sem r a
- type InterpretersFor (es :: [Effect]) (r :: [Effect]) = forall a. Sem (Append es r) a -> Sem r a
- class Member (t :: Effect) (r :: EffectRow)
- data Sem (r :: EffectRow) a
- type Effect = (Type -> Type) -> Type -> Type
- type EffectRow = [Effect]
- newtype Embed (m :: Type -> Type) (z :: Type -> Type) a where
- asyncToIOFinal :: forall (r :: EffectRow) a. Member (Final IO) r => Sem (Async ': r) a -> Sem r a
- sequenceConcurrently :: forall t (r :: EffectRow) a. (Traversable t, Member Async r) => t (Sem r a) -> Sem r (t (Maybe a))
- cancel :: forall (r :: EffectRow) a. Member Async r => Async a -> Sem r ()
- await :: forall (r :: EffectRow) a. Member Async r => Async a -> Sem r a
- async :: forall (r :: EffectRow) a. Member Async r => Sem r a -> Sem r (Async (Maybe a))
- data Async (m :: Type -> Type) a
- execAtomicStateViaState :: forall s (r :: [(Type -> Type) -> Type -> Type]) a. s -> Sem ((AtomicState s :: (Type -> Type) -> Type -> Type) ': r) a -> Sem r s
- evalAtomicStateViaState :: forall s (r :: [(Type -> Type) -> Type -> Type]) a. s -> Sem ((AtomicState s :: (Type -> Type) -> Type -> Type) ': r) a -> Sem r a
- runAtomicStateViaState :: forall s (r :: [(Type -> Type) -> Type -> Type]) a. s -> Sem ((AtomicState s :: (Type -> Type) -> Type -> Type) ': r) a -> Sem r (s, a)
- atomicStateToState :: forall s (r :: EffectRow) a. Member (State s :: (Type -> Type) -> Type -> Type) r => Sem ((AtomicState s :: (Type -> Type) -> Type -> Type) ': r) a -> Sem r a
- atomicStateToIO :: forall s (r :: EffectRow) a. Member (Embed IO) r => s -> Sem ((AtomicState s :: (Type -> Type) -> Type -> Type) ': r) a -> Sem r (s, a)
- runAtomicStateTVar :: forall (r :: EffectRow) s a. Member (Embed IO) r => TVar s -> Sem ((AtomicState s :: (Type -> Type) -> Type -> Type) ': r) a -> Sem r a
- runAtomicStateIORef :: forall s (r :: EffectRow) a. Member (Embed IO) r => IORef s -> Sem ((AtomicState s :: (Type -> Type) -> Type -> Type) ': r) a -> Sem r a
- atomicModify' :: forall s (r :: EffectRow). Member (AtomicState s :: (Type -> Type) -> Type -> Type) r => (s -> s) -> Sem r ()
- atomicModify :: forall s (r :: EffectRow). Member (AtomicState s :: (Type -> Type) -> Type -> Type) r => (s -> s) -> Sem r ()
- atomicPut :: forall s (r :: EffectRow). Member (AtomicState s :: (Type -> Type) -> Type -> Type) r => s -> Sem r ()
- atomicState' :: forall s a (r :: EffectRow). Member (AtomicState s :: (Type -> Type) -> Type -> Type) r => (s -> (s, a)) -> Sem r a
- atomicGets :: forall s s' (r :: EffectRow). Member (AtomicState s :: (Type -> Type) -> Type -> Type) r => (s -> s') -> Sem r s'
- atomicGet :: forall s (r :: EffectRow). Member (AtomicState s :: (Type -> Type) -> Type -> Type) r => Sem r s
- atomicState :: forall s a (r :: EffectRow). Member (AtomicState s :: (Type -> Type) -> Type -> Type) r => (s -> (s, a)) -> Sem r a
- data AtomicState s (m :: k) a
- errorToIOFinal :: forall e (r :: EffectRow) a. Member (Final IO) r => Sem ((Error e :: (Type -> Type) -> Type -> Type) ': r) a -> Sem r (Either e a)
- mapError :: forall e1 e2 (r :: EffectRow) a. Member (Error e2 :: (Type -> Type) -> Type -> Type) r => (e1 -> e2) -> Sem ((Error e1 :: (Type -> Type) -> Type -> Type) ': r) a -> Sem r a
- runError :: forall e (r :: [(Type -> Type) -> Type -> Type]) a. Sem ((Error e :: (Type -> Type) -> Type -> Type) ': r) a -> Sem r (Either e a)
- catchJust :: forall e (r :: EffectRow) b a. Member (Error e :: (Type -> Type) -> Type -> Type) r => (e -> Maybe b) -> Sem r a -> (b -> Sem r a) -> Sem r a
- tryJust :: forall e (r :: EffectRow) b a. Member (Error e :: (Type -> Type) -> Type -> Type) r => (e -> Maybe b) -> Sem r a -> Sem r (Either b a)
- try :: forall e (r :: EffectRow) a. Member (Error e :: (Type -> Type) -> Type -> Type) r => Sem r a -> Sem r (Either e a)
- note :: forall e (r :: EffectRow) a. Member (Error e :: (Type -> Type) -> Type -> Type) r => e -> Maybe a -> Sem r a
- fromExceptionSemVia :: forall exc err (r :: EffectRow) a. (Exception exc, Member (Error err :: (Type -> Type) -> Type -> Type) r, Member (Final IO) r) => (exc -> err) -> Sem r a -> Sem r a
- fromExceptionSem :: forall e (r :: EffectRow) a. (Exception e, Member (Error e :: (Type -> Type) -> Type -> Type) r, Member (Final IO) r) => Sem r a -> Sem r a
- fromExceptionVia :: forall exc err (r :: EffectRow) a. (Exception exc, Member (Error err :: (Type -> Type) -> Type -> Type) r, Member (Embed IO) r) => (exc -> err) -> IO a -> Sem r a
- fromException :: forall e (r :: EffectRow) a. (Exception e, Member (Error e :: (Type -> Type) -> Type -> Type) r, Member (Embed IO) r) => IO a -> Sem r a
- fromEitherM :: forall e m (r :: EffectRow) a. (Member (Error e :: (Type -> Type) -> Type -> Type) r, Member (Embed m) r) => m (Either e a) -> Sem r a
- fromEither :: forall e (r :: EffectRow) a. Member (Error e :: (Type -> Type) -> Type -> Type) r => Either e a -> Sem r a
- catch :: forall e (r :: EffectRow) a. Member (Error e :: (Type -> Type) -> Type -> Type) r => Sem r a -> (e -> Sem r a) -> Sem r a
- throw :: forall e (r :: EffectRow) a. Member (Error e :: (Type -> Type) -> Type -> Type) r => e -> Sem r a
- data Error e (m :: k -> Type) (a :: k)
- failToEmbed :: forall (m :: Type -> Type) (r :: EffectRow) a. (Member (Embed m) r, MonadFail m) => Sem ((Fail :: (Type -> Type) -> Type -> TYPE LiftedRep) ': r) a -> Sem r a
- failToNonDet :: forall (r :: EffectRow) a. Member NonDet r => Sem ((Fail :: (Type -> Type) -> Type -> TYPE LiftedRep) ': r) a -> Sem r a
- failToError :: forall e (r :: EffectRow) a. Member (Error e :: (Type -> Type) -> Type -> Type) r => (String -> e) -> Sem ((Fail :: (Type -> Type) -> Type -> TYPE LiftedRep) ': r) a -> Sem r a
- runFail :: forall (r :: [(Type -> Type) -> Type -> TYPE LiftedRep]) a. Sem ((Fail :: (Type -> Type) -> Type -> TYPE LiftedRep) ': r) a -> Sem r (Either String a)
- data Fail (m :: k) (a :: k1)
- runInputSem :: forall i (r :: EffectRow) a. Sem r i -> Sem ((Input i :: (Type -> Type) -> Type -> Type) ': r) a -> Sem r a
- runInputList :: forall i (r :: [(Type -> Type) -> Type -> Type]) a. [i] -> Sem ((Input (Maybe i) :: (Type -> Type) -> Type -> Type) ': r) a -> Sem r a
- runInputConst :: forall i (r :: [(Type -> Type) -> TYPE LiftedRep -> Type]) a. i -> Sem ((Input i :: (Type -> Type) -> TYPE LiftedRep -> Type) ': r) a -> Sem r a
- inputs :: forall i j (r :: EffectRow). Member (Input i :: (Type -> Type) -> Type -> Type) r => (i -> j) -> Sem r j
- input :: forall i (r :: EffectRow). Member (Input i :: (Type -> Type) -> Type -> Type) r => Sem r i
- data Input (i :: k) (m :: k1) (a :: k)
- runOutputSem :: forall o (r :: EffectRow) a. (o -> Sem r ()) -> Sem ((Output o :: (Type -> Type) -> Type -> Type) ': r) a -> Sem r a
- runOutputBatched :: forall o (r :: EffectRow) a. Member (Output [o] :: (Type -> Type) -> Type -> Type) r => Int -> Sem ((Output o :: (Type -> Type) -> Type -> Type) ': r) a -> Sem r a
- ignoreOutput :: forall o (r :: [(Type -> Type) -> Type -> Type]) a. Sem ((Output o :: (Type -> Type) -> Type -> Type) ': r) a -> Sem r a
- outputToIOMonoidAssocR :: forall o m (r :: EffectRow) a. (Monoid m, Member (Embed IO) r) => (o -> m) -> Sem ((Output o :: (Type -> Type) -> Type -> Type) ': r) a -> Sem r (m, a)
- outputToIOMonoid :: forall o m (r :: EffectRow) a. (Monoid m, Member (Embed IO) r) => (o -> m) -> Sem ((Output o :: (Type -> Type) -> Type -> Type) ': r) a -> Sem r (m, a)
- runOutputMonoidTVar :: forall o m (r :: EffectRow) a. (Monoid m, Member (Embed IO) r) => TVar m -> (o -> m) -> Sem ((Output o :: (Type -> Type) -> Type -> Type) ': r) a -> Sem r a
- runOutputMonoidIORef :: forall o m (r :: EffectRow) a. (Monoid m, Member (Embed IO) r) => IORef m -> (o -> m) -> Sem ((Output o :: (Type -> Type) -> Type -> Type) ': r) a -> Sem r a
- runLazyOutputMonoidAssocR :: forall o m (r :: [(Type -> Type) -> Type -> Type]) a. Monoid m => (o -> m) -> Sem ((Output o :: (Type -> Type) -> Type -> Type) ': r) a -> Sem r (m, a)
- runOutputMonoidAssocR :: forall o m (r :: [(Type -> Type) -> Type -> Type]) a. Monoid m => (o -> m) -> Sem ((Output o :: (Type -> Type) -> Type -> Type) ': r) a -> Sem r (m, a)
- runLazyOutputMonoid :: forall o m (r :: [(Type -> Type) -> Type -> Type]) a. Monoid m => (o -> m) -> Sem ((Output o :: (Type -> Type) -> Type -> Type) ': r) a -> Sem r (m, a)
- runOutputMonoid :: forall o m (r :: [(Type -> Type) -> Type -> Type]) a. Monoid m => (o -> m) -> Sem ((Output o :: (Type -> Type) -> Type -> Type) ': r) a -> Sem r (m, a)
- runLazyOutputList :: forall o (r :: [(Type -> Type) -> Type -> Type]) a. Sem ((Output o :: (Type -> Type) -> Type -> Type) ': r) a -> Sem r ([o], a)
- runOutputList :: forall o (r :: [(Type -> Type) -> Type -> Type]) a. Sem ((Output o :: (Type -> Type) -> Type -> Type) ': r) a -> Sem r ([o], a)
- output :: forall o (r :: EffectRow). Member (Output o :: (Type -> Type) -> Type -> Type) r => o -> Sem r ()
- data Output o (m :: k) a
- inputToReader :: forall i (r :: EffectRow) a. Member (Reader i) r => Sem ((Input i :: (Type -> Type) -> Type -> Type) ': r) a -> Sem r a
- runReader :: forall i (r :: [(Type -> Type) -> Type -> Type]) a. i -> Sem (Reader i ': r) a -> Sem r a
- asks :: forall i j (r :: EffectRow). Member (Reader i) r => (i -> j) -> Sem r j
- local :: forall i (r :: EffectRow) a. Member (Reader i) r => (i -> i) -> Sem r a -> Sem r a
- ask :: forall i (r :: EffectRow). Member (Reader i) r => Sem r i
- data Reader i (m :: Type -> Type) a
- runResource :: forall (r :: [(Type -> Type) -> Type -> Type]) a. Sem (Resource ': r) a -> Sem r a
- resourceToIOFinal :: forall (r :: EffectRow) a. Member (Final IO) r => Sem (Resource ': r) a -> Sem r a
- onException :: forall (r :: EffectRow) a b. Member Resource r => Sem r a -> Sem r b -> Sem r a
- finally :: forall (r :: EffectRow) a b. Member Resource r => Sem r a -> Sem r b -> Sem r a
- bracket_ :: forall (r :: EffectRow) a b c. Member Resource r => Sem r a -> Sem r b -> Sem r c -> Sem r c
- bracketOnError :: forall (r :: EffectRow) a c b. Member Resource r => Sem r a -> (a -> Sem r c) -> (a -> Sem r b) -> Sem r b
- bracket :: forall (r :: EffectRow) a c b. Member Resource r => Sem r a -> (a -> Sem r c) -> (a -> Sem r b) -> Sem r b
- data Resource (m :: Type -> Type) a
- module Polysemy.Scoped
- hoistStateIntoStateT :: forall s (r :: [(Type -> Type) -> Type -> Type]) a. Sem ((State s :: (Type -> Type) -> Type -> Type) ': r) a -> StateT s (Sem r) a
- stateToST :: forall s st (r :: EffectRow) a. Member (Embed (ST st)) r => s -> Sem ((State s :: (Type -> Type) -> Type -> Type) ': r) a -> Sem r (s, a)
- runStateSTRef :: forall s st (r :: EffectRow) a. Member (Embed (ST st)) r => STRef st s -> Sem ((State s :: (Type -> Type) -> Type -> Type) ': r) a -> Sem r a
- stateToIO :: forall s (r :: EffectRow) a. Member (Embed IO) r => s -> Sem ((State s :: (Type -> Type) -> Type -> Type) ': r) a -> Sem r (s, a)
- runStateIORef :: forall s (r :: EffectRow) a. Member (Embed IO) r => IORef s -> Sem ((State s :: (Type -> Type) -> Type -> Type) ': r) a -> Sem r a
- execLazyState :: forall s (r :: [(Type -> Type) -> Type -> Type]) a. s -> Sem ((State s :: (Type -> Type) -> Type -> Type) ': r) a -> Sem r s
- evalLazyState :: forall s (r :: [(Type -> Type) -> Type -> Type]) a. s -> Sem ((State s :: (Type -> Type) -> Type -> Type) ': r) a -> Sem r a
- runLazyState :: forall s (r :: [(Type -> Type) -> Type -> Type]) a. s -> Sem ((State s :: (Type -> Type) -> Type -> Type) ': r) a -> Sem r (s, a)
- execState :: forall s (r :: [(Type -> Type) -> Type -> Type]) a. s -> Sem ((State s :: (Type -> Type) -> Type -> Type) ': r) a -> Sem r s
- evalState :: forall s (r :: [(Type -> Type) -> Type -> Type]) a. s -> Sem ((State s :: (Type -> Type) -> Type -> Type) ': r) a -> Sem r a
- runState :: forall s (r :: [(Type -> Type) -> Type -> Type]) a. s -> Sem ((State s :: (Type -> Type) -> Type -> Type) ': r) a -> Sem r (s, a)
- modify' :: forall s (r :: EffectRow). Member (State s :: (Type -> Type) -> Type -> Type) r => (s -> s) -> Sem r ()
- modify :: forall s (r :: EffectRow). Member (State s :: (Type -> Type) -> Type -> Type) r => (s -> s) -> Sem r ()
- gets :: forall s a (r :: EffectRow). Member (State s :: (Type -> Type) -> Type -> Type) r => (s -> a) -> Sem r a
- put :: forall s (r :: EffectRow). Member (State s :: (Type -> Type) -> Type -> Type) r => s -> Sem r ()
- get :: forall s (r :: EffectRow). Member (State s :: (Type -> Type) -> Type -> Type) r => Sem r s
- data State s (m :: k) a
- retag :: forall {k1} {k2} (k3 :: k1) (k4 :: k2) (e :: (Type -> Type) -> Type -> Type) (r :: EffectRow) a. Member (Tagged k4 e) r => Sem (Tagged k3 e ': r) a -> Sem r a
- untag :: forall {k1} (k2 :: k1) (e :: (Type -> Type) -> Type -> Type) (r :: [(Type -> Type) -> Type -> Type]) a. Sem (Tagged k2 e ': r) a -> Sem (e ': r) a
- tagged :: forall {k1} (k2 :: k1) (e :: Effect) (r :: [Effect]) a. Sem (e ': r) a -> Sem (Tagged k2 e ': r) a
- tag :: forall {k1} (k2 :: k1) (e :: (Type -> Type) -> Type -> Type) (r :: EffectRow) a. Member (Tagged k2 e) r => Sem (e ': r) a -> Sem r a
- data Tagged (k3 :: k) (e :: k1 -> k2 -> Type) (m :: k1) (a :: k2)
- writerToIOAssocRFinal :: forall o (r :: EffectRow) a. (Monoid o, Member (Final IO) r) => Sem (Writer o ': r) a -> Sem r (o, a)
- writerToIOFinal :: forall o (r :: EffectRow) a. (Monoid o, Member (Final IO) r) => Sem (Writer o ': r) a -> Sem r (o, a)
- runWriterTVar :: forall o (r :: EffectRow) a. (Monoid o, Member (Final IO) r) => TVar o -> Sem (Writer o ': r) a -> Sem r a
- runLazyWriterAssocR :: forall o (r :: [(Type -> Type) -> Type -> Type]) a. Monoid o => Sem (Writer o ': r) a -> Sem r (o, a)
- runWriterAssocR :: forall o (r :: [(Type -> Type) -> Type -> Type]) a. Monoid o => Sem (Writer o ': r) a -> Sem r (o, a)
- runLazyWriter :: forall o (r :: [(Type -> Type) -> Type -> Type]) a. Monoid o => Sem (Writer o ': r) a -> Sem r (o, a)
- runWriter :: forall o (r :: [(Type -> Type) -> Type -> Type]) a. Monoid o => Sem (Writer o ': r) a -> Sem r (o, a)
- outputToWriter :: forall o (r :: EffectRow) a. Member (Writer o) r => Sem ((Output o :: (Type -> Type) -> Type -> Type) ': r) a -> Sem r a
- censor :: forall o (r :: EffectRow) a. Member (Writer o) r => (o -> o) -> Sem r a -> Sem r a
- writerToEndoWriter :: forall o (r :: EffectRow) a. (Monoid o, Member (Writer (Endo o)) r) => Sem (Writer o ': r) a -> Sem r a
- pass :: forall o (r :: EffectRow) a. Member (Writer o) r => Sem r (o -> o, a) -> Sem r a
- listen :: forall o (r :: EffectRow) a. Member (Writer o) r => Sem r a -> Sem r (o, a)
- tell :: forall o (r :: EffectRow). Member (Writer o) r => o -> Sem r ()
- data Writer o (m :: Type -> Type) a
- type (++) a b = Append a b
- unitT :: Functor f => Sem (WithTactics e f m r) (f ())
Documentation
module Incipit.Exception
module IncipitBase
embedToFinal :: forall (m :: Type -> Type) (r :: EffectRow) a. (Member (Final m) r, Functor m) => Sem (Embed m ': r) a -> Sem r a #
runFinal :: Monad m => Sem '[Final m] a -> m a #
Lower a Sem containing only a single lifted, final Monad into that
 monad.
If you also need to process an Embed membedToFinal.
Since: polysemy-1.2.0.0
embedFinal :: forall m (r :: EffectRow) a. (Member (Final m) r, Functor m) => m a -> Sem r a #
withWeavingToFinal admits an implementation of embed.
Just like embed, you are discouraged from using this in application code.
Since: polysemy-1.2.0.0
data Final (m :: Type -> Type) (z :: Type -> Type) a #
An effect for embedding higher-order actions in the final target monad of the effect stack.
This is very useful for writing interpreters that interpret higher-order effects in terms of the final monad.
Final is more powerful than Embed, but is also less flexible
 to interpret (compare runEmbedded with finalToFinal).
 If you only need the power of embed, then you should use Embed instead.
Beware: Final actions are interpreted as actions of the final monad,
 and the effectful state visible to
 withWeavingToFinal / withStrategicToFinal
 / interpretFinal
 is that of all interpreters run in order to produce the final monad.
This means that any interpreter built using Final will not
 respect local/global state semantics based on the order of
 interpreters run. You should signal interpreters that make use of
 Final by adding a - suffix to the names of these.Final
State semantics of effects that are not interpreted in terms of the final monad will always appear local to effects that are interpreted in terms of the final monad.
State semantics between effects that are interpreted in terms of the final monad depend on the final monad. For example, if the final monad is a monad transformer stack, then state semantics will depend on the order monad transformers are stacked.
Since: polysemy-1.2.0.0
transform :: forall e1 e2 (r :: EffectRow) a. Member e2 r => (forall (rInitial :: EffectRow) x. e1 (Sem rInitial) x -> e2 (Sem rInitial) x) -> Sem (e1 ': r) a -> Sem r a #
Transform an effect e1 into an effect e2 that is already somewhere
 inside of the stack.
Since: polysemy-1.2.3.0
rewrite :: forall e1 e2 (r :: [Effect]) a. (forall (rInitial :: EffectRow) x. e1 (Sem rInitial) x -> e2 (Sem rInitial) x) -> Sem (e1 ': r) a -> Sem (e2 ': r) a #
Rewrite an effect e1 directly into e2, and put it on the top of the
 effect stack.
Since: polysemy-1.2.3.0
Arguments
| :: forall e (r :: EffectRow) a. Member e r | |
| => (forall x (rInitial :: EffectRow). e (Sem rInitial) x -> Tactical e (Sem rInitial) r x) | A natural transformation from the handled effect to other effects
 already in  | 
| -> Sem r a | Unlike  | 
| -> Sem r a | 
Arguments
| :: forall e (r :: EffectRow) a. (Member e r, FirstOrder e "intercept") | |
| => (forall x (rInitial :: EffectRow). e (Sem rInitial) x -> Sem r x) | A natural transformation from the handled effect to other effects
 already in  | 
| -> Sem r a | |
| -> Sem r a | 
Like interpret, but instead of handling the effect, allows responding to
 the effect while leaving it unhandled. This allows you, for example, to
 intercept other effects and insert logic around them.
Arguments
| :: forall e1 (e2 :: Effect) (e3 :: Effect) (e4 :: Effect) (r :: [Effect]) a. FirstOrder e1 "reinterpret3" | |
| => (forall (rInitial :: EffectRow) x. e1 (Sem rInitial) x -> Sem (e2 ': (e3 ': (e4 ': r))) x) | A natural transformation from the handled effect to the new effects. | 
| -> Sem (e1 ': r) a | |
| -> Sem (e2 ': (e3 ': (e4 ': r))) a | 
Like reinterpret, but introduces three intermediary effects.
Arguments
| :: forall e1 (e2 :: Effect) (e3 :: Effect) (e4 :: Effect) (r :: [Effect]) a. (forall (rInitial :: EffectRow) x. e1 (Sem rInitial) x -> Tactical e1 (Sem rInitial) (e2 ': (e3 ': (e4 ': r))) x) | A natural transformation from the handled effect to the new effects. | 
| -> Sem (e1 ': r) a | |
| -> Sem (e2 ': (e3 ': (e4 ': r))) a | 
Like reinterpret3, but for higher-order effects.
See the notes on Tactical for how to use this function.
Arguments
| :: forall e1 (e2 :: Effect) (e3 :: Effect) (r :: [Effect]) a. FirstOrder e1 "reinterpret2" | |
| => (forall (rInitial :: EffectRow) x. e1 (Sem rInitial) x -> Sem (e2 ': (e3 ': r)) x) | A natural transformation from the handled effect to the new effects. | 
| -> Sem (e1 ': r) a | |
| -> Sem (e2 ': (e3 ': r)) a | 
Like reinterpret, but introduces two intermediary effects.
Arguments
| :: forall e1 (e2 :: Effect) (e3 :: Effect) (r :: [Effect]) a. (forall (rInitial :: EffectRow) x. e1 (Sem rInitial) x -> Tactical e1 (Sem rInitial) (e2 ': (e3 ': r)) x) | A natural transformation from the handled effect to the new effects. | 
| -> Sem (e1 ': r) a | |
| -> Sem (e2 ': (e3 ': r)) a | 
Like reinterpret2, but for higher-order effects.
See the notes on Tactical for how to use this function.
Arguments
| :: forall e1 (e2 :: Effect) (r :: [Effect]) a. FirstOrder e1 "reinterpret" | |
| => (forall (rInitial :: EffectRow) x. e1 (Sem rInitial) x -> Sem (e2 ': r) x) | A natural transformation from the handled effect to the new effect. | 
| -> Sem (e1 ': r) a | |
| -> Sem (e2 ': r) a | 
Like interpret, but instead of removing the effect e, reencodes it in
 some new effect f. This function will fuse when followed by
 runState, meaning it's free to reinterpret in terms of
 the State effect and immediately run it.
Arguments
| :: forall e1 (e2 :: Effect) (r :: [Effect]) a. (forall (rInitial :: EffectRow) x. e1 (Sem rInitial) x -> Tactical e1 (Sem rInitial) (e2 ': r) x) | A natural transformation from the handled effect to the new effect. | 
| -> Sem (e1 ': r) a | |
| -> Sem (e2 ': r) a | 
Like reinterpret, but for higher-order effects.
See the notes on Tactical for how to use this function.
Arguments
| :: forall e (r :: [Effect]) a. FirstOrder e "interpret" | |
| => (forall (rInitial :: EffectRow) x. e (Sem rInitial) x -> Sem r x) | A natural transformation from the handled effect to other effects
 already in  | 
| -> Sem (e ': r) a | |
| -> Sem r a | 
The simplest way to produce an effect handler. Interprets an effect e by
 transforming it into other effects inside of r.
Like makeSem, but does not provide type signatures and fixities. This
 can be used to attach Haddock comments to individual arguments for each
 generated function.
data Output o m a where
  Output :: o -> Output o m ()
makeSem_ ''Output
-- | Output the value @o@.
output :: forall o r
       .  Member (Output o) r
       => o         -- ^ Value to output.
       -> Sem r ()  -- ^ No result.
Because of limitations in Template Haskell, signatures have to follow some rules to work properly:
- makeSem_must be used before the explicit type signatures
- signatures have to specify argument of Semrepresenting union of effects asr(e.g.Semr ()
- all arguments in effect's type constructor have to follow naming scheme from data constructor's declaration:
data Foo e m a where FooC1 :: Foo x m () FooC2 :: Foo (Maybe x) m ()
should have x in type signature of fooC1:
fooC1 :: forall x r. Member (Foo x) r => Sem r ()
and Maybe x in signature of fooC2:
fooC2 :: forall x r. Member (Foo (Maybe x)) r => Sem r ()
- all effect's type variables and rhave to be explicitly quantified usingforall(order is not important)
These restrictions may be removed in the future, depending on changes to the compiler.
Change in (TODO(Sandy): version): in case of GADTs, signatures now only use names from data constructor's type and not from type constructor declaration.
Since: polysemy-0.1.2.0
If T is a GADT representing an effect algebra, as described in the
 module documentation for Polysemy, $( automatically
 generates a smart constructor for every data constructor of makeSem ''T)T. This also
 works for data family instances. Names of smart constructors are created by
 changing first letter to lowercase or removing prefix : in case of
 operators. Fixity declaration is preserved for both normal names and
 operators.
Since: polysemy-0.1.2.0
Arguments
| :: forall m f (r :: [Effect]) (e :: Effect) a b. (a -> m b) | The monadic continuation to lift. This is usually a parameter in your effect. Continuations executed via  | 
| -> f a | |
| -> Sem (WithTactics e f m r) (f b) | 
Lift a kleisli action into the stateful environment.
 You can use bindTSimple to execute an effect parameter of the form
 a -> m b by providing the result of a runTSimple or another
 bindTSimple.
This is a less flexible but significantly simpler variant of bindT.
 Instead of returning a Sem kleisli action corresponding to the
 provided kleisli action, bindTSimple runs the kleisli action immediately.
Since: polysemy-1.5.0.0
Arguments
| :: forall m a (e :: Effect) (r :: [Effect]). m a | The monadic action to lift. This is usually a parameter in your effect. | 
| -> Tactical e m r a | 
Run a monadic action in a Tactical environment. The stateful environment
 used will be the same one that the effect is initally run in.
 Use bindTSimple if you'd prefer to explicitly manage your stateful
 environment.
This is a less flexible but significantly simpler variant of runT.
 Instead of returning a Sem action corresponding to the provided action,
 runTSimple runs the action immediately.
Since: polysemy-1.5.0.0
Arguments
| :: forall m a (e :: Effect) f (r :: [Effect]). m a | The monadic action to lift. This is usually a parameter in your effect. | 
| -> Sem (WithTactics e f m r) (Sem (e ': r) (f a)) | 
pureT :: forall f a (e :: Effect) (m :: Type -> Type) (r :: [Effect]). Functor f => a -> Sem (WithTactics e f m r) (f a) #
Lift a value into Tactical.
getInspectorT :: forall (e :: Effect) (f :: Type -> TYPE LiftedRep) (m :: Type -> Type) (r :: [Effect]). Sem (WithTactics e f m r) (Inspector f) #
Get a natural transformation capable of potentially inspecting values
 inside of f. Binding the result of getInspectorT produces a function that
 can sometimes peek inside values returned by bindT.
This is often useful for running callback functions that are not managed by polysemy code.
Example
We can use the result of getInspectorT to "undo" pureT (or any of the other
 Tactical functions):
ins <-getInspectorTfa <-pureT"hello" fb <-pureTTrue let a =inspectins fa -- Just "hello" b =inspectins fb -- Just True
getInitialStateT :: forall f (m :: Type -> Type) (r :: [Effect]) (e :: Effect). Sem (WithTactics e f m r) (f ()) #
type Tactical (e :: Effect) (m :: Type -> Type) (r :: [Effect]) x = forall (f :: Type -> Type). Functor f => Sem (WithTactics e f m r) (f x) #
Tactical is an environment in which you're capable of explicitly
 threading higher-order effect states. This is provided by the (internal)
 effect Tactics, which is capable of rewriting monadic actions so they run
 in the correct stateful environment.
Inside a Tactical, you're capable of running pureT, runT and bindT
 which are the main tools for rewriting monadic stateful environments.
For example, consider trying to write an interpreter for
 Resource, whose effect is defined as:
dataResourcem a whereBracket:: m a -> (a -> m ()) -> (a -> m b) ->Resourcem b
Here we have an m a which clearly needs to be run first, and then
 subsequently call the a -> m () and a -> m b arguments. In a Tactical
 environment, we can write the threading code thusly:
Bracketalloc dealloc use -> do alloc' <-runTalloc dealloc' <-bindTdealloc use' <-bindTuse
where
alloc' ::Sem(Resource': r) (f a1) dealloc' :: f a1 ->Sem(Resource': r) (f ()) use' :: f a1 ->Sem(Resource': r) (f x)
The f type here is existential and corresponds to "whatever
 state the other effects want to keep track of." f is always
 a Functor.
alloc', dealloc' and use' are now in a form that can be
 easily consumed by your interpreter. At this point, simply bind
 them in the desired order and continue on your merry way.
We can see from the types of dealloc' and use' that since they both
 consume a f a1, they must run in the same stateful environment. This
 means, for illustration, any puts run inside the use
 block will not be visible inside of the dealloc block.
Power users may explicitly use getInitialStateT and bindT to construct
 whatever data flow they'd like; although this is usually unnecessary.
type WithTactics (e :: Effect) (f :: Type -> TYPE LiftedRep) (m :: Type -> Type) (r :: [Effect]) = (Tactics f m (e ': r) :: (Type -> Type) -> TYPE LiftedRep -> Type) ': r #
Convenience type alias, see Tactical.
newtype Inspector (f :: Type -> Type) #
A container for inspect. See the documentation for getInspectorT.
Constructors
| Inspector | |
| Fields 
 | |
embed :: forall m (r :: EffectRow) a. Member (Embed m) r => m a -> Sem r a #
Embed a monadic action m in Sem.
Since: polysemy-1.0.0.0
send :: forall e (r :: EffectRow) a. Member e r => e (Sem r) a -> Sem r a #
Execute an action of an effect.
This is primarily used to create methods for actions of effects:
data FooBar m a where Foo :: String -> m a -> FooBar m a Bar :: FooBar m Int foo :: Member FooBar r => String -> Sem r a -> Sem r a foo s m = send (Foo s m) bar :: Member FooBar r => Sem r Int bar = send Bar
makeSem allows you to eliminate this boilerplate.
@since TODO
insertAt :: forall (index :: Nat) (inserted :: [Effect]) (head :: [Effect]) (oldTail :: [Effect]) (tail :: [Effect]) (old :: [Effect]) (full :: [Effect]) a. (ListOfLength index head, WhenStuck index (InsertAtUnprovidedIndex :: Constraint), old ~ Append head oldTail, tail ~ Append inserted oldTail, full ~ Append head tail, InsertAtIndex index head tail oldTail full inserted) => Sem old a -> Sem full a #
Introduce a set of effects into Sem at the index i, before the effect
 that previously occupied that position. This is intended to be used with a
 type application:
let sem1 :: Sem [e1, e2, e3, e4, e5] a sem1 = insertAt @2 (sem0 :: Sem [e1, e2, e5] a)
Since: polysemy-1.6.0.0
subsume :: forall (e :: Effect) (r :: EffectRow) a. Member e r => Sem (e ': r) a -> Sem r a #
Interprets an effect in terms of another identical effect.
This is useful for defining interpreters that use reinterpretH
 without immediately consuming the newly introduced effect.
 Using such an interpreter recursively may result in duplicate effects,
 which may then be eliminated using subsume.
For a version that can introduce an arbitrary number of new effects and
 reorder existing ones, see subsume_.
Since: polysemy-1.2.0.0
subsume_ :: forall (r :: EffectRow) (r' :: EffectRow) a. Subsume r r' => Sem r a -> Sem r' a #
Allows reordering and adding known effects on top of the effect stack, as
 long as the polymorphic "tail" of new stack is a raise-d version of the
 original one. This function is highly polymorphic, so it may be a good idea
 to use its more concrete version (subsume), fitting functions from the
 raise family or type annotations to avoid vague errors in ambiguous
 contexts.
Since: polysemy-1.4.0.0
raise3Under :: forall (e4 :: Effect) (e1 :: Effect) (e2 :: Effect) (e3 :: Effect) (r :: [Effect]) a. Sem (e1 ': (e2 ': (e3 ': r))) a -> Sem (e1 ': (e2 ': (e3 ': (e4 ': r)))) a #
Like raise, but introduces an effect three levels underneath the head
 of the list.
Since: polysemy-1.4.0.0
raise2Under :: forall (e3 :: Effect) (e1 :: Effect) (e2 :: Effect) (r :: [Effect]) a. Sem (e1 ': (e2 ': r)) a -> Sem (e1 ': (e2 ': (e3 ': r))) a #
Like raise, but introduces an effect two levels underneath the head of
 the list.
Since: polysemy-1.4.0.0
raiseUnder3 :: forall (e2 :: Effect) (e3 :: Effect) (e4 :: Effect) (e1 :: Effect) (r :: [Effect]) a. Sem (e1 ': r) a -> Sem (e1 ': (e2 ': (e3 ': (e4 ': r)))) a #
Like raise, but introduces three new effects underneath the head of the
 list.
Since: polysemy-1.2.0.0
raiseUnder2 :: forall (e2 :: Effect) (e3 :: Effect) (e1 :: Effect) (r :: [Effect]) a. Sem (e1 ': r) a -> Sem (e1 ': (e2 ': (e3 ': r))) a #
Like raise, but introduces two new effects underneath the head of the
 list.
Since: polysemy-1.2.0.0
raiseUnder :: forall (e2 :: Effect) (e1 :: Effect) (r :: [Effect]) a. Sem (e1 ': r) a -> Sem (e1 ': (e2 ': r)) a #
Like raise, but introduces a new effect underneath the head of the
 list. See raiseUnder2 or raiseUnder3 for introducing more effects. If
 you need to introduce even more of them, check out subsume_.
raiseUnder can be used in order to turn transformative interpreters
 into reinterpreters. This is especially useful if you're writing an
 interpreter which introduces an intermediary effect, and then want to use
 an existing interpreter on that effect.
For example, given:
fooToBar ::MemberBar r =>Sem(Foo ': r) a ->Semr a runBar ::Sem(Bar ': r) a ->Semr a
You can write:
runFoo ::Sem(Foo ': r) a ->Semr a runFoo = runBar -- Consume Bar . fooToBar -- Interpret Foo in terms of the new Bar .raiseUnder-- Introduces Bar under Foo
Since: polysemy-1.2.0.0
raise_ :: forall (r :: EffectRow) (r' :: EffectRow) a. Raise r r' => Sem r a -> Sem r' a #
Introduce an arbitrary number of effects on top of the effect stack. This
 function is highly polymorphic, so it may be good idea to use its more
 concrete versions (like raise) or type annotations to avoid vague errors
 in ambiguous contexts.
Since: polysemy-1.4.0.0
type family Members (es :: [Effect]) (r :: EffectRow) where ... #
Makes constraints of functions that use multiple effects shorter by
 translating single list of effects into multiple Member constraints:
foo ::Members'[OutputInt ,OutputBool ,StateString ] r =>Semr ()
translates into:
foo :: (Member(OutputInt) r ,Member(OutputBool) r ,Member(StateString) r ) =>Semr ()
Since: polysemy-0.1.2.0
type InterpreterFor (e :: Effect) (r :: [Effect]) = forall a. Sem (e ': r) a -> Sem r a #
Type synonym for interpreters that consume an effect without changing the return value. Offered for user convenience.
r Is kept polymorphic so it's possible to place constraints upon it:
teletypeToIO ::Member(Embed IO) r =>InterpreterForTeletype r
type InterpretersFor (es :: [Effect]) (r :: [Effect]) = forall a. Sem (Append es r) a -> Sem r a #
Variant of InterpreterFor that takes a list of effects.
 @since 1.5.0.0
class Member (t :: Effect) (r :: EffectRow) #
This class indicates that an effect must be present in the caller's stack. It is the main mechanism by which a program defines its effect dependencies.
Minimal complete definition
membership'
Instances
| Member t z => Member t (_1 ': z) | |
| Defined in Polysemy.Internal.Union Methods membership' :: ElemOf t (_1 ': z) | |
| Member t (t ': z) | |
| Defined in Polysemy.Internal.Union Methods membership' :: ElemOf t (t ': z) | |
The Sem monad handles computations of arbitrary extensible effects.
 A value of type Sem r describes a program with the capabilities of
 r. For best results, r should always be kept polymorphic, but you can
 add capabilities via the Member constraint.
The value of the Sem monad is that it allows you to write programs
 against a set of effects without a predefined meaning, and provide that
 meaning later. For example, unlike with mtl, you can decide to interpret an
 Error effect traditionally as an Either, or instead
 as (a significantly faster) IO Exception. These
 interpretations (and others that you might add) may be used interchangeably
 without needing to write any newtypes or Monad instances. The only
 change needed to swap interpretations is to change a call from
 runError to errorToIOFinal.
The effect stack r can contain arbitrary other monads inside of it. These
 monads are lifted into effects via the Embed effect. Monadic values can be
 lifted into a Sem via embed.
Higher-order actions of another monad can be lifted into higher-order actions
 of Sem via the Final effect, which is more powerful
 than Embed, but also less flexible to interpret.
A Sem can be interpreted as a pure value (via run) or as any
 traditional Monad (via runM or runFinal).
 Each effect E comes equipped with some interpreters of the form:
runE ::Sem(E ': r) a ->Semr a
which is responsible for removing the effect E from the effect stack. It
 is the order in which you call the interpreters that determines the
 monomorphic representation of the r parameter.
Order of interpreters can be important - it determines behaviour of effects that manipulate state or change control flow. For example, when interpreting this action:
>>>:{example :: Members '[State String, Error String] r => Sem r String example = do put "start" let throwing, catching :: Members '[State String, Error String] r => Sem r String throwing = do modify (++"-throw") throw "error" get catching = do modify (++"-catch") get catch @String throwing (\ _ -> catching) :}
when handling Error first, state is preserved after error
 occurs:
>>>:{example & runError & fmap (either id id) & evalState "" & runM & (print =<<) :} "start-throw-catch"
while handling State first discards state in such cases:
>>>:{example & evalState "" & runError & fmap (either id id) & runM & (print =<<) :} "start-catch"
A good rule of thumb is to handle effects which should have "global" behaviour over other effects later in the chain.
After all of your effects are handled, you'll be left with either
 a Sem '[] aSem '[ Embed m ] aSem '[ Final m ] arun, runM, and
 runFinal.
Examples
As an example of keeping r polymorphic, we can consider the type
Member(StateString) r =>Semr ()
to be a program with access to
get::Semr Stringput:: String ->Semr ()
methods.
By also adding a
Member(ErrorBool) r
constraint on r, we gain access to the
throw:: Bool ->Semr acatch::Semr a -> (Bool ->Semr a) ->Semr a
functions as well.
In this sense, a Member (State s) rMonadState s mSem monad may have
 an arbitrary number of the same effect.
For example, we can write a Sem program which can output either
 Ints or Bools:
foo :: (Member(OutputInt) r ,Member(OutputBool) r ) =>Semr () foo = dooutput@Int 5outputTrue
Notice that we must use -XTypeApplications to specify that we'd like to
 use the (Output Int) effect.
Since: polysemy-0.1.2.0
Instances
| Member (Fail :: (Type -> Type) -> Type -> TYPE LiftedRep) r => MonadFail (Sem r) | Since: polysemy-1.1.0.0 | 
| Defined in Polysemy.Internal | |
| Member Fixpoint r => MonadFix (Sem r) | |
| Defined in Polysemy.Internal | |
| Member (Embed IO) r => MonadIO (Sem r) | This instance will only lift  | 
| Defined in Polysemy.Internal | |
| Member NonDet r => Alternative (Sem r) | |
| Applicative (Sem f) | |
| Functor (Sem f) | |
| Monad (Sem f) | |
| Member NonDet r => MonadPlus (Sem r) | Since: polysemy-0.2.1.0 | 
| Monoid a => Monoid (Sem f a) | Since: polysemy-1.6.0.0 | 
| Semigroup a => Semigroup (Sem f a) | Since: polysemy-1.6.0.0 | 
newtype Embed (m :: Type -> Type) (z :: Type -> Type) a where #
An effect which allows a regular Monad m into the Sem
 ecosystem. Monadic actions in m can be lifted into Sem via
 embed.
For example, you can use this effect to lift IO actions directly into
 Sem:
embed(putStrLn "hello") ::Member(EmbedIO) r =>Semr ()
That being said, you lose out on a significant amount of the benefits of
 Sem by using embed directly in application code; doing
 so will tie your application code directly to the underlying monad, and
 prevent you from interpreting it differently. For best results, only use
 Embed in your effect interpreters.
Consider using trace and traceToIO as
 a substitute for using putStrLn directly.
Since: polysemy-1.0.0.0
sequenceConcurrently :: forall t (r :: EffectRow) a. (Traversable t, Member Async r) => t (Sem r a) -> Sem r (t (Maybe a)) #
Perform a sequence of effectful actions concurrently.
Since: polysemy-1.2.2.0
cancel :: forall (r :: EffectRow) a. Member Async r => Async a -> Sem r () #
Cancel the thread referenced by the given handle.
await :: forall (r :: EffectRow) a. Member Async r => Async a -> Sem r a #
Wait for the thread referenced by the given handle to terminate.
async :: forall (r :: EffectRow) a. Member Async r => Sem r a -> Sem r (Async (Maybe a)) #
Run the given action asynchronously and return a thread handle.
execAtomicStateViaState :: forall s (r :: [(Type -> Type) -> Type -> Type]) a. s -> Sem ((AtomicState s :: (Type -> Type) -> Type -> Type) ': r) a -> Sem r s #
Execute an AtomicState with local state semantics, discarding
 the notion of atomicity, by transforming it into State and running it
 with the provided initial state.
@since v1.7.0.0
evalAtomicStateViaState :: forall s (r :: [(Type -> Type) -> Type -> Type]) a. s -> Sem ((AtomicState s :: (Type -> Type) -> Type -> Type) ': r) a -> Sem r a #
Evaluate an AtomicState with local state semantics, discarding
 the notion of atomicity, by transforming it into State and running it
 with the provided initial state.
@since v1.7.0.0
runAtomicStateViaState :: forall s (r :: [(Type -> Type) -> Type -> Type]) a. s -> Sem ((AtomicState s :: (Type -> Type) -> Type -> Type) ': r) a -> Sem r (s, a) #
Run an AtomicState with local state semantics, discarding
 the notion of atomicity, by transforming it into State and running it
 with the provided initial state.
@since v1.7.0.0
atomicStateToState :: forall s (r :: EffectRow) a. Member (State s :: (Type -> Type) -> Type -> Type) r => Sem ((AtomicState s :: (Type -> Type) -> Type -> Type) ': r) a -> Sem r a #
Transform an AtomicState effect to a State effect, discarding
 the notion of atomicity.
atomicStateToIO :: forall s (r :: EffectRow) a. Member (Embed IO) r => s -> Sem ((AtomicState s :: (Type -> Type) -> Type -> Type) ': r) a -> Sem r (s, a) #
Run an AtomicState effect in terms of atomic operations
 in IO.
Internally, this simply creates a new IORef, passes it to
 runAtomicStateIORef, and then returns the result and the final value
 of the IORef.
Beware: As this uses an IORef internally,
 all other effects will have local
 state semantics in regards to AtomicState effects
 interpreted this way.
 For example, throw and catch will
 never revert atomicModifys, even if runError is used
 after atomicStateToIO.
Since: polysemy-1.2.0.0
runAtomicStateTVar :: forall (r :: EffectRow) s a. Member (Embed IO) r => TVar s -> Sem ((AtomicState s :: (Type -> Type) -> Type -> Type) ': r) a -> Sem r a #
Run an AtomicState effect by transforming it into atomic operations
 over a TVar.
runAtomicStateIORef :: forall s (r :: EffectRow) a. Member (Embed IO) r => IORef s -> Sem ((AtomicState s :: (Type -> Type) -> Type -> Type) ': r) a -> Sem r a #
Run an AtomicState effect by transforming it into atomic operations
 over an IORef.
atomicModify' :: forall s (r :: EffectRow). Member (AtomicState s :: (Type -> Type) -> Type -> Type) r => (s -> s) -> Sem r () #
A variant of atomicModify in which the computation is strict in the
 new state.
atomicModify :: forall s (r :: EffectRow). Member (AtomicState s :: (Type -> Type) -> Type -> Type) r => (s -> s) -> Sem r () #
Modify the state lazily.
atomicPut :: forall s (r :: EffectRow). Member (AtomicState s :: (Type -> Type) -> Type -> Type) r => s -> Sem r () #
Replace the state with the given value.
atomicState' :: forall s a (r :: EffectRow). Member (AtomicState s :: (Type -> Type) -> Type -> Type) r => (s -> (s, a)) -> Sem r a #
A variant of atomicState in which the computation is strict in the new
 state and return value.
atomicGets :: forall s s' (r :: EffectRow). Member (AtomicState s :: (Type -> Type) -> Type -> Type) r => (s -> s') -> Sem r s' #
Since: polysemy-1.2.2.0
atomicGet :: forall s (r :: EffectRow). Member (AtomicState s :: (Type -> Type) -> Type -> Type) r => Sem r s #
Get the state.
atomicState :: forall s a (r :: EffectRow). Member (AtomicState s :: (Type -> Type) -> Type -> Type) r => (s -> (s, a)) -> Sem r a #
Run a state action.
data AtomicState s (m :: k) a #
A variant of State that supports atomic operations.
Since: polysemy-1.1.0.0
errorToIOFinal :: forall e (r :: EffectRow) a. Member (Final IO) r => Sem ((Error e :: (Type -> Type) -> Type -> Type) ': r) a -> Sem r (Either e a) #
mapError :: forall e1 e2 (r :: EffectRow) a. Member (Error e2 :: (Type -> Type) -> Type -> Type) r => (e1 -> e2) -> Sem ((Error e1 :: (Type -> Type) -> Type -> Type) ': r) a -> Sem r a #
Transform one Error into another. This function can be used to aggregate
 multiple errors into a single type.
Since: polysemy-1.0.0.0
runError :: forall e (r :: [(Type -> Type) -> Type -> Type]) a. Sem ((Error e :: (Type -> Type) -> Type -> Type) ': r) a -> Sem r (Either e a) #
tryJust :: forall e (r :: EffectRow) b a. Member (Error e :: (Type -> Type) -> Type -> Type) r => (e -> Maybe b) -> Sem r a -> Sem r (Either b a) #
try :: forall e (r :: EffectRow) a. Member (Error e :: (Type -> Type) -> Type -> Type) r => Sem r a -> Sem r (Either e a) #
note :: forall e (r :: EffectRow) a. Member (Error e :: (Type -> Type) -> Type -> Type) r => e -> Maybe a -> Sem r a #
fromExceptionSemVia :: forall exc err (r :: EffectRow) a. (Exception exc, Member (Error err :: (Type -> Type) -> Type -> Type) r, Member (Final IO) r) => (exc -> err) -> Sem r a -> Sem r a #
Like fromExceptionSem, but with the ability to transform the exception
 before turning it into an Error.
fromExceptionSem :: forall e (r :: EffectRow) a. (Exception e, Member (Error e :: (Type -> Type) -> Type -> Type) r, Member (Final IO) r) => Sem r a -> Sem r a #
fromExceptionVia :: forall exc err (r :: EffectRow) a. (Exception exc, Member (Error err :: (Type -> Type) -> Type -> Type) r, Member (Embed IO) r) => (exc -> err) -> IO a -> Sem r a #
Like fromException, but with the ability to transform the exception
 before turning it into an Error.
fromException :: forall e (r :: EffectRow) a. (Exception e, Member (Error e :: (Type -> Type) -> Type -> Type) r, Member (Embed IO) r) => IO a -> Sem r a #
fromEitherM :: forall e m (r :: EffectRow) a. (Member (Error e :: (Type -> Type) -> Type -> Type) r, Member (Embed m) r) => m (Either e a) -> Sem r a #
A combinator doing embed and fromEither at the same time. Useful for
 interoperating with IO.
Since: polysemy-0.5.1.0
fromEither :: forall e (r :: EffectRow) a. Member (Error e :: (Type -> Type) -> Type -> Type) r => Either e a -> Sem r a #
catch :: forall e (r :: EffectRow) a. Member (Error e :: (Type -> Type) -> Type -> Type) r => Sem r a -> (e -> Sem r a) -> Sem r a #
Recover from an error that might have been thrown in the higher-order action given by the first argument by passing the error to the handler given by the second argument.
throw :: forall e (r :: EffectRow) a. Member (Error e :: (Type -> Type) -> Type -> Type) r => e -> Sem r a #
Short-circuit the current program using the given error value.
data Error e (m :: k -> Type) (a :: k) #
This effect abstracts the throwing and catching of errors, leaving
 it up to the interpreter whether to use exceptions or monad transformers
 like ExceptT to perform the short-circuiting mechanism.
failToEmbed :: forall (m :: Type -> Type) (r :: EffectRow) a. (Member (Embed m) r, MonadFail m) => Sem ((Fail :: (Type -> Type) -> Type -> TYPE LiftedRep) ': r) a -> Sem r a #
failToNonDet :: forall (r :: EffectRow) a. Member NonDet r => Sem ((Fail :: (Type -> Type) -> Type -> TYPE LiftedRep) ': r) a -> Sem r a #
failToError :: forall e (r :: EffectRow) a. Member (Error e :: (Type -> Type) -> Type -> Type) r => (String -> e) -> Sem ((Fail :: (Type -> Type) -> Type -> TYPE LiftedRep) ': r) a -> Sem r a #
runFail :: forall (r :: [(Type -> Type) -> Type -> TYPE LiftedRep]) a. Sem ((Fail :: (Type -> Type) -> Type -> TYPE LiftedRep) ': r) a -> Sem r (Either String a) #
Run a Fail effect purely.
data Fail (m :: k) (a :: k1) #
This effect abstracts the concept of MonadFail,
 which is a built-in mechanism that converts pattern matching errors to
 calls to the current monad's instance of that class.
The instance defined in Polysemy.Internal uses this effect to catch those errors.
runInputSem :: forall i (r :: EffectRow) a. Sem r i -> Sem ((Input i :: (Type -> Type) -> Type -> Type) ': r) a -> Sem r a #
Runs an Input effect by evaluating a monadic action for each request.
runInputList :: forall i (r :: [(Type -> Type) -> Type -> Type]) a. [i] -> Sem ((Input (Maybe i) :: (Type -> Type) -> Type -> Type) ': r) a -> Sem r a #
runInputConst :: forall i (r :: [(Type -> Type) -> TYPE LiftedRep -> Type]) a. i -> Sem ((Input i :: (Type -> Type) -> TYPE LiftedRep -> Type) ': r) a -> Sem r a #
Run an Input effect by always giving back the same value.
inputs :: forall i j (r :: EffectRow). Member (Input i :: (Type -> Type) -> Type -> Type) r => (i -> j) -> Sem r j #
Apply a function to an input, cf. asks
input :: forall i (r :: EffectRow). Member (Input i :: (Type -> Type) -> Type -> Type) r => Sem r i #
Get the next available message.
data Input (i :: k) (m :: k1) (a :: k) #
An effect which can provide input to an application. Useful for dealing with streaming input.
runOutputSem :: forall o (r :: EffectRow) a. (o -> Sem r ()) -> Sem ((Output o :: (Type -> Type) -> Type -> Type) ': r) a -> Sem r a #
Runs an Output effect by running a monadic action for each of its
 values.
runOutputBatched :: forall o (r :: EffectRow) a. Member (Output [o] :: (Type -> Type) -> Type -> Type) r => Int -> Sem ((Output o :: (Type -> Type) -> Type -> Type) ': r) a -> Sem r a #
ignoreOutput :: forall o (r :: [(Type -> Type) -> Type -> Type]) a. Sem ((Output o :: (Type -> Type) -> Type -> Type) ': r) a -> Sem r a #
Run an Output effect by ignoring it.
Since: polysemy-1.0.0.0
outputToIOMonoidAssocR :: forall o m (r :: EffectRow) a. (Monoid m, Member (Embed IO) r) => (o -> m) -> Sem ((Output o :: (Type -> Type) -> Type -> Type) ': r) a -> Sem r (m, a) #
Like outputToIOMonoid, but right-associates uses of <>.
This asymptotically improves performance if the time complexity of <> for
 the Monoid depends only on the size of the first argument.
You should always use this instead of outputToIOMonoid if the monoid
 is a list, such as String.
Beware: As this uses an IORef internally,
 all other effects will have local
 state semantics in regards to Output effects
 interpreted this way.
 For example, throw and catch will
 never revert outputs, even if runError is used
 after outputToIOMonoidAssocR.
Since: polysemy-1.2.0.0
outputToIOMonoid :: forall o m (r :: EffectRow) a. (Monoid m, Member (Embed IO) r) => (o -> m) -> Sem ((Output o :: (Type -> Type) -> Type -> Type) ': r) a -> Sem r (m, a) #
Run an Output effect in terms of atomic operations
 in IO.
Internally, this simply creates a new IORef, passes it to
 runOutputMonoidIORef, and then returns the result and the final value
 of the IORef.
Beware: As this uses an IORef internally,
 all other effects will have local
 state semantics in regards to Output effects
 interpreted this way.
 For example, throw and catch will
 never revert outputs, even if runError is used
 after outputToIOMonoid.
Since: polysemy-1.2.0.0
runOutputMonoidTVar :: forall o m (r :: EffectRow) a. (Monoid m, Member (Embed IO) r) => TVar m -> (o -> m) -> Sem ((Output o :: (Type -> Type) -> Type -> Type) ': r) a -> Sem r a #
runOutputMonoidIORef :: forall o m (r :: EffectRow) a. (Monoid m, Member (Embed IO) r) => IORef m -> (o -> m) -> Sem ((Output o :: (Type -> Type) -> Type -> Type) ': r) a -> Sem r a #
runLazyOutputMonoidAssocR :: forall o m (r :: [(Type -> Type) -> Type -> Type]) a. Monoid m => (o -> m) -> Sem ((Output o :: (Type -> Type) -> Type -> Type) ': r) a -> Sem r (m, a) #
Like runLazyOutputMonoid, but right-associates uses of <>.
This asymptotically improves performance if the time complexity of <> for
 the Monoid depends only on the size of the first argument.
You should always use this instead of runLazyOutputMonoid if the monoid
 is a list, such as String.
Warning: This inherits the nasty space leak issue of
 WriterT! Don't use this if you don't have to.
Since: polysemy-1.3.0.0
runOutputMonoidAssocR :: forall o m (r :: [(Type -> Type) -> Type -> Type]) a. Monoid m => (o -> m) -> Sem ((Output o :: (Type -> Type) -> Type -> Type) ': r) a -> Sem r (m, a) #
Like runOutputMonoid, but right-associates uses of <>.
This asymptotically improves performance if the time complexity of <> for
 the Monoid depends only on the size of the first argument.
You should always use this instead of runOutputMonoid if the monoid
 is a list, such as String.
Since: polysemy-1.1.0.0
runLazyOutputMonoid :: forall o m (r :: [(Type -> Type) -> Type -> Type]) a. Monoid m => (o -> m) -> Sem ((Output o :: (Type -> Type) -> Type -> Type) ': r) a -> Sem r (m, a) #
runOutputMonoid :: forall o m (r :: [(Type -> Type) -> Type -> Type]) a. Monoid m => (o -> m) -> Sem ((Output o :: (Type -> Type) -> Type -> Type) ': r) a -> Sem r (m, a) #
Run an Output effect by transforming it into a monoid.
Since: polysemy-1.0.0.0
runLazyOutputList :: forall o (r :: [(Type -> Type) -> Type -> Type]) a. Sem ((Output o :: (Type -> Type) -> Type -> Type) ': r) a -> Sem r ([o], a) #
runOutputList :: forall o (r :: [(Type -> Type) -> Type -> Type]) a. Sem ((Output o :: (Type -> Type) -> Type -> Type) ': r) a -> Sem r ([o], a) #
Run an Output effect by transforming it into a list of its values.
Since: polysemy-1.0.0.0
output :: forall o (r :: EffectRow). Member (Output o :: (Type -> Type) -> Type -> Type) r => o -> Sem r () #
Output a message.
An effect capable of sending messages. Useful for streaming output and for logging.
inputToReader :: forall i (r :: EffectRow) a. Member (Reader i) r => Sem ((Input i :: (Type -> Type) -> Type -> Type) ': r) a -> Sem r a #
runReader :: forall i (r :: [(Type -> Type) -> Type -> Type]) a. i -> Sem (Reader i ': r) a -> Sem r a #
Run a Reader effect with a constant value.
asks :: forall i j (r :: EffectRow). Member (Reader i) r => (i -> j) -> Sem r j #
Apply a function to the environment and return the result.
local :: forall i (r :: EffectRow) a. Member (Reader i) r => (i -> i) -> Sem r a -> Sem r a #
Transform the environment.
runResource :: forall (r :: [(Type -> Type) -> Type -> Type]) a. Sem (Resource ': r) a -> Sem r a #
Run a Resource effect purely.
Since: polysemy-1.0.0.0
resourceToIOFinal :: forall (r :: EffectRow) a. Member (Final IO) r => Sem (Resource ': r) a -> Sem r a #
Arguments
| :: forall (r :: EffectRow) a b. Member Resource r | |
| => Sem r a | computation to run first | 
| -> Sem r b | computation to run afterward if an exception was raised | 
| -> Sem r a | 
Like bracketOnError, but for the simple case of one computation to run
 afterward.
Since: polysemy-0.4.0.0
Arguments
| :: forall (r :: EffectRow) a b. Member Resource r | |
| => Sem r a | computation to run first | 
| -> Sem r b | computation to run afterward (even if an exception was raised) | 
| -> Sem r a | 
Like bracket, but for the simple case of one computation to run
 afterward.
Since: polysemy-0.4.0.0
bracketOnError :: forall (r :: EffectRow) a c b. Member Resource r => Sem r a -> (a -> Sem r c) -> (a -> Sem r b) -> Sem r b #
Allocate a resource, use it, and clean it up afterwards if an error occurred.
bracket :: forall (r :: EffectRow) a c b. Member Resource r => Sem r a -> (a -> Sem r c) -> (a -> Sem r b) -> Sem r b #
Allocate a resource, use it, and clean it up afterwards.
data Resource (m :: Type -> Type) a #
An effect capable of providing bracket semantics. Interpreters for this
 will successfully run the deallocation action even in the presence of other
 short-circuiting effects.
module Polysemy.Scoped
hoistStateIntoStateT :: forall s (r :: [(Type -> Type) -> Type -> Type]) a. Sem ((State s :: (Type -> Type) -> Type -> Type) ': r) a -> StateT s (Sem r) a #
stateToST :: forall s st (r :: EffectRow) a. Member (Embed (ST st)) r => s -> Sem ((State s :: (Type -> Type) -> Type -> Type) ': r) a -> Sem r (s, a) #
Run an State effect in terms of operations
 in ST.
Internally, this simply creates a new STRef, passes it to
 runStateSTRef, and then returns the result and the final value
 of the STRef.
Beware: As this uses an STRef internally,
 all other effects will have local
 state semantics in regards to State effects
 interpreted this way.
 For example, throw and catch will
 never revert puts, even if runError is used
 after stateToST.
When not using the plugin, one must introduce the existential st type to
 stateToST, so that the resulting type after runM can be resolved into
 forall st. ST st (s, a) for use with runST. Doing so requires
 -XScopedTypeVariables.
stResult :: forall s a. (s, a) stResult = runST ( (runM $ stateToST @_ @st undefined $ pure undefined) :: forall st. ST st (s, a) )
Since: polysemy-1.3.0.0
runStateSTRef :: forall s st (r :: EffectRow) a. Member (Embed (ST st)) r => STRef st s -> Sem ((State s :: (Type -> Type) -> Type -> Type) ': r) a -> Sem r a #
stateToIO :: forall s (r :: EffectRow) a. Member (Embed IO) r => s -> Sem ((State s :: (Type -> Type) -> Type -> Type) ': r) a -> Sem r (s, a) #
Run an State effect in terms of operations
 in IO.
Internally, this simply creates a new IORef, passes it to
 runStateIORef, and then returns the result and the final value
 of the IORef.
Note: This is not safe in a concurrent setting, as modify isn't atomic.
 If you need operations over the state to be atomic,
 use atomicStateToIO instead.
Beware: As this uses an IORef internally,
 all other effects will have local
 state semantics in regards to State effects
 interpreted this way.
 For example, throw and catch will
 never revert puts, even if runError is used
 after stateToIO.
Since: polysemy-1.2.0.0
runStateIORef :: forall s (r :: EffectRow) a. Member (Embed IO) r => IORef s -> Sem ((State s :: (Type -> Type) -> Type -> Type) ': r) a -> Sem r a #
Run a State effect by transforming it into operations over an IORef.
Note: This is not safe in a concurrent setting, as modify isn't atomic.
 If you need operations over the state to be atomic,
 use runAtomicStateIORef or
 runAtomicStateTVar instead.
Since: polysemy-1.0.0.0
execLazyState :: forall s (r :: [(Type -> Type) -> Type -> Type]) a. s -> Sem ((State s :: (Type -> Type) -> Type -> Type) ': r) a -> Sem r s #
Run a State effect with local state, lazily.
Since: polysemy-1.2.3.1
evalLazyState :: forall s (r :: [(Type -> Type) -> Type -> Type]) a. s -> Sem ((State s :: (Type -> Type) -> Type -> Type) ': r) a -> Sem r a #
Run a State effect with local state, lazily.
Since: polysemy-1.0.0.0
runLazyState :: forall s (r :: [(Type -> Type) -> Type -> Type]) a. s -> Sem ((State s :: (Type -> Type) -> Type -> Type) ': r) a -> Sem r (s, a) #
Run a State effect with local state, lazily.
execState :: forall s (r :: [(Type -> Type) -> Type -> Type]) a. s -> Sem ((State s :: (Type -> Type) -> Type -> Type) ': r) a -> Sem r s #
Run a State effect with local state.
Since: polysemy-1.2.3.1
evalState :: forall s (r :: [(Type -> Type) -> Type -> Type]) a. s -> Sem ((State s :: (Type -> Type) -> Type -> Type) ': r) a -> Sem r a #
Run a State effect with local state.
Since: polysemy-1.0.0.0
runState :: forall s (r :: [(Type -> Type) -> Type -> Type]) a. s -> Sem ((State s :: (Type -> Type) -> Type -> Type) ': r) a -> Sem r (s, a) #
Run a State effect with local state.
modify' :: forall s (r :: EffectRow). Member (State s :: (Type -> Type) -> Type -> Type) r => (s -> s) -> Sem r () #
A variant of modify in which the computation is strict in the
 new state.
modify :: forall s (r :: EffectRow). Member (State s :: (Type -> Type) -> Type -> Type) r => (s -> s) -> Sem r () #
Modify the state.
gets :: forall s a (r :: EffectRow). Member (State s :: (Type -> Type) -> Type -> Type) r => (s -> a) -> Sem r a #
Apply a function to the state and return the result.
put :: forall s (r :: EffectRow). Member (State s :: (Type -> Type) -> Type -> Type) r => s -> Sem r () #
Update the state.
get :: forall s (r :: EffectRow). Member (State s :: (Type -> Type) -> Type -> Type) r => Sem r s #
Get the state.
An effect for providing statefulness. Note that unlike mtl's
 StateT, there is no restriction that the State
 effect corresponds necessarily to local state. It could could just as well
 be interrpeted in terms of HTTP requests or database access.
Interpreters which require statefulness can reinterpret
 themselves in terms of State, and subsequently call runState.
retag :: forall {k1} {k2} (k3 :: k1) (k4 :: k2) (e :: (Type -> Type) -> Type -> Type) (r :: EffectRow) a. Member (Tagged k4 e) r => Sem (Tagged k3 e ': r) a -> Sem r a #
untag :: forall {k1} (k2 :: k1) (e :: (Type -> Type) -> Type -> Type) (r :: [(Type -> Type) -> Type -> Type]) a. Sem (Tagged k2 e ': r) a -> Sem (e ': r) a #
Run a Tagged k ee
tagged :: forall {k1} (k2 :: k1) (e :: Effect) (r :: [Effect]) a. Sem (e ': r) a -> Sem (Tagged k2 e ': r) a #
A reinterpreting version of tag.
tag :: forall {k1} (k2 :: k1) (e :: (Type -> Type) -> Type -> Type) (r :: EffectRow) a. Member (Tagged k2 e) r => Sem (e ': r) a -> Sem r a #
Tag uses of an effect, effectively gaining access to the tagged effect locally.
This may be used to create tagged- variants of regular actions.
For example:
taggedLocal :: forall k i r a
             . Member (Tagged k (Reader i)) r
            => (i -> i)
            -> Sem r a
            -> Sem r a
taggedLocal f m =
  tag @k @(Reader i) $ local @i f (raise m)
data Tagged (k3 :: k) (e :: k1 -> k2 -> Type) (m :: k1) (a :: k2) #
An effect for annotating effects and disambiguating identical effects.
writerToIOAssocRFinal :: forall o (r :: EffectRow) a. (Monoid o, Member (Final IO) r) => Sem (Writer o ': r) a -> Sem r (o, a) #
Like writerToIOFinal. but right-associates uses of <>.
This asymptotically improves performance if the time complexity of <>
 for the Monoid depends only on the size of the first argument.
You should always use this instead of writerToIOFinal if the monoid
 is a list, such as String.
Beware: Effects that aren't interpreted in terms of IO
 will have local state semantics in regards to Writer effects
 interpreted this way. See Final.
Since: polysemy-1.2.0.0
writerToIOFinal :: forall o (r :: EffectRow) a. (Monoid o, Member (Final IO) r) => Sem (Writer o ': r) a -> Sem r (o, a) #
Run a Writer effect by transforming it into atomic operations
 through final IO.
Internally, this simply creates a new TVar, passes it to
 runWriterTVar, and then returns the result and the final value
 of the TVar.
Beware: Effects that aren't interpreted in terms of IO
 will have local state semantics in regards to Writer effects
 interpreted this way. See Final.
Since: polysemy-1.2.0.0
runWriterTVar :: forall o (r :: EffectRow) a. (Monoid o, Member (Final IO) r) => TVar o -> Sem (Writer o ': r) a -> Sem r a #
runLazyWriterAssocR :: forall o (r :: [(Type -> Type) -> Type -> Type]) a. Monoid o => Sem (Writer o ': r) a -> Sem r (o, a) #
Like runLazyWriter, but right-associates uses of <>.
This asymptotically improves performance if the time complexity of <>
 for the Monoid depends only on the size of the first argument.
You should always use this instead of runLazyWriter if the monoid
 is a list, such as String.
Warning: This inherits the nasty space leak issue of
 WriterT! Don't use this if you don't have to.
Since: polysemy-1.3.0.0
runWriterAssocR :: forall o (r :: [(Type -> Type) -> Type -> Type]) a. Monoid o => Sem (Writer o ': r) a -> Sem r (o, a) #
runLazyWriter :: forall o (r :: [(Type -> Type) -> Type -> Type]) a. Monoid o => Sem (Writer o ': r) a -> Sem r (o, a) #
runWriter :: forall o (r :: [(Type -> Type) -> Type -> Type]) a. Monoid o => Sem (Writer o ': r) a -> Sem r (o, a) #
outputToWriter :: forall o (r :: EffectRow) a. Member (Writer o) r => Sem ((Output o :: (Type -> Type) -> Type -> Type) ': r) a -> Sem r a #
censor :: forall o (r :: EffectRow) a. Member (Writer o) r => (o -> o) -> Sem r a -> Sem r a #
Since: polysemy-0.7.0.0
writerToEndoWriter :: forall o (r :: EffectRow) a. (Monoid o, Member (Writer (Endo o)) r) => Sem (Writer o ': r) a -> Sem r a #
pass :: forall o (r :: EffectRow) a. Member (Writer o) r => Sem r (o -> o, a) -> Sem r a #
Run the given action and apply the function it returns to the log.
listen :: forall o (r :: EffectRow) a. Member (Writer o) r => Sem r a -> Sem r (o, a) #
Return the log produced by the higher-order action.
tell :: forall o (r :: EffectRow). Member (Writer o) r => o -> Sem r () #
Write a message to the log.