in-other-words-0.2.0.0: A higher-order effect system where the sky's the limit
Safe HaskellNone
LanguageHaskell2010

Control.Effect.Internal.Writer

Synopsis

Documentation

data Tell o :: Effect where Source #

An effect for arbitrary output.

Constructors

Tell :: o -> Tell o m () 

Instances

Instances details
(Monoid w, Carrier m, Threaders '[SteppedThreads] m p) => PrimHandler ListenSteppedH (ListenPrim w) (SteppedC (Tell w) m) Source # 
Instance details

Defined in Control.Effect.Internal.Intercept

data Listen o :: Effect where Source #

An effect for hearing what a computation has to tell.

Constructors

Listen :: m a -> Listen o m (o, a) 

Instances

Instances details
Eff (ListenPrim w) m => Handler ListenSteppedH (Listen w) m Source # 
Instance details

Defined in Control.Effect.Internal.Intercept

newtype Pass o :: Effect where Source #

An effect for altering what a computation tells.

Constructors

Pass :: m (o -> o, a) -> Pass o m a 

newtype TellC o m a Source #

Constructors

TellC 

Fields

Instances

Instances details
MonadBase b m => MonadBase b (TellC o m) Source # 
Instance details

Defined in Control.Effect.Internal.Writer

Methods

liftBase :: b α -> TellC o m α #

(MonadBaseControl b m, Monoid o) => MonadBaseControl b (TellC o m) Source # 
Instance details

Defined in Control.Effect.Internal.Writer

Associated Types

type StM (TellC o m) a #

Methods

liftBaseWith :: (RunInBase (TellC o m) b -> b a) -> TellC o m a #

restoreM :: StM (TellC o m) a -> TellC o m a #

MonadTrans (TellC o) Source # 
Instance details

Defined in Control.Effect.Internal.Writer

Methods

lift :: Monad m => m a -> TellC o m a #

Monoid o => MonadTransControl (TellC o) Source # 
Instance details

Defined in Control.Effect.Internal.Writer

Associated Types

type StT (TellC o) a #

Methods

liftWith :: Monad m => (Run (TellC o) -> m a) -> TellC o m a #

restoreT :: Monad m => m (StT (TellC o) a) -> TellC o m a #

Monad m => Monad (TellC o m) Source # 
Instance details

Defined in Control.Effect.Internal.Writer

Methods

(>>=) :: TellC o m a -> (a -> TellC o m b) -> TellC o m b #

(>>) :: TellC o m a -> TellC o m b -> TellC o m b #

return :: a -> TellC o m a #

Functor m => Functor (TellC o m) Source # 
Instance details

Defined in Control.Effect.Internal.Writer

Methods

fmap :: (a -> b) -> TellC o m a -> TellC o m b #

(<$) :: a -> TellC o m b -> TellC o m a #

MonadFix m => MonadFix (TellC o m) Source # 
Instance details

Defined in Control.Effect.Internal.Writer

Methods

mfix :: (a -> TellC o m a) -> TellC o m a #

MonadFail m => MonadFail (TellC o m) Source # 
Instance details

Defined in Control.Effect.Internal.Writer

Methods

fail :: String -> TellC o m a #

Monad m => Applicative (TellC o m) Source # 
Instance details

Defined in Control.Effect.Internal.Writer

Methods

pure :: a -> TellC o m a #

(<*>) :: TellC o m (a -> b) -> TellC o m a -> TellC o m b #

liftA2 :: (a -> b -> c) -> TellC o m a -> TellC o m b -> TellC o m c #

(*>) :: TellC o m a -> TellC o m b -> TellC o m b #

(<*) :: TellC o m a -> TellC o m b -> TellC o m a #

MonadIO m => MonadIO (TellC o m) Source # 
Instance details

Defined in Control.Effect.Internal.Writer

Methods

liftIO :: IO a -> TellC o m a #

MonadPlus m => Alternative (TellC o m) Source # 
Instance details

Defined in Control.Effect.Internal.Writer

Methods

empty :: TellC o m a #

(<|>) :: TellC o m a -> TellC o m a -> TellC o m a #

some :: TellC o m a -> TellC o m [a] #

many :: TellC o m a -> TellC o m [a] #

MonadPlus m => MonadPlus (TellC o m) Source # 
Instance details

Defined in Control.Effect.Internal.Writer

Methods

mzero :: TellC o m a #

mplus :: TellC o m a -> TellC o m a -> TellC o m a #

MonadThrow m => MonadThrow (TellC o m) Source # 
Instance details

Defined in Control.Effect.Internal.Writer

Methods

throwM :: Exception e => e -> TellC o m a #

(Monoid o, MonadCatch m) => MonadCatch (TellC o m) Source # 
Instance details

Defined in Control.Effect.Internal.Writer

Methods

catch :: Exception e => TellC o m a -> (e -> TellC o m a) -> TellC o m a #

(Monoid o, MonadMask m) => MonadMask (TellC o m) Source # 
Instance details

Defined in Control.Effect.Internal.Writer

Methods

mask :: ((forall a. TellC o m a -> TellC o m a) -> TellC o m b) -> TellC o m b #

uninterruptibleMask :: ((forall a. TellC o m a -> TellC o m a) -> TellC o m b) -> TellC o m b #

generalBracket :: TellC o m a -> (a -> ExitCase b -> TellC o m c) -> (a -> TellC o m b) -> TellC o m (b, c) #

(Carrier m, Monoid o, Threads (WriterT o) (Prims m)) => Carrier (TellC o m) Source # 
Instance details

Defined in Control.Effect.Internal.Writer

Associated Types

type Derivs (TellC o m) :: [Effect] Source #

type Prims (TellC o m) :: [Effect] Source #

Methods

algPrims :: Algebra' (Prims (TellC o m)) (TellC o m) a Source #

reformulate :: Monad z => Reformulation' (Derivs (TellC o m)) (Prims (TellC o m)) (TellC o m) z a Source #

algDerivs :: Algebra' (Derivs (TellC o m)) (TellC o m) a Source #

type StT (TellC o) a Source # 
Instance details

Defined in Control.Effect.Internal.Writer

type StT (TellC o) a = (a, o)
type Derivs (TellC o m) Source # 
Instance details

Defined in Control.Effect.Internal.Writer

type Derivs (TellC o m) = Tell o ': Derivs m
type Prims (TellC o m) Source # 
Instance details

Defined in Control.Effect.Internal.Writer

type Prims (TellC o m) = Prims m
type StM (TellC o m) a Source # 
Instance details

Defined in Control.Effect.Internal.Writer

type StM (TellC o m) a = StM m (a, o)

newtype ListenC o m a Source #

Constructors

ListenC 

Fields

Instances

Instances details
MonadBase b m => MonadBase b (ListenC o m) Source # 
Instance details

Defined in Control.Effect.Internal.Writer

Methods

liftBase :: b α -> ListenC o m α #

(MonadBaseControl b m, Monoid o) => MonadBaseControl b (ListenC o m) Source # 
Instance details

Defined in Control.Effect.Internal.Writer

Associated Types

type StM (ListenC o m) a #

Methods

liftBaseWith :: (RunInBase (ListenC o m) b -> b a) -> ListenC o m a #

restoreM :: StM (ListenC o m) a -> ListenC o m a #

MonadTrans (ListenC o) Source # 
Instance details

Defined in Control.Effect.Internal.Writer

Methods

lift :: Monad m => m a -> ListenC o m a #

Monoid o => MonadTransControl (ListenC o) Source # 
Instance details

Defined in Control.Effect.Internal.Writer

Associated Types

type StT (ListenC o) a #

Methods

liftWith :: Monad m => (Run (ListenC o) -> m a) -> ListenC o m a #

restoreT :: Monad m => m (StT (ListenC o) a) -> ListenC o m a #

Monad m => Monad (ListenC o m) Source # 
Instance details

Defined in Control.Effect.Internal.Writer

Methods

(>>=) :: ListenC o m a -> (a -> ListenC o m b) -> ListenC o m b #

(>>) :: ListenC o m a -> ListenC o m b -> ListenC o m b #

return :: a -> ListenC o m a #

Functor m => Functor (ListenC o m) Source # 
Instance details

Defined in Control.Effect.Internal.Writer

Methods

fmap :: (a -> b) -> ListenC o m a -> ListenC o m b #

(<$) :: a -> ListenC o m b -> ListenC o m a #

MonadFix m => MonadFix (ListenC o m) Source # 
Instance details

Defined in Control.Effect.Internal.Writer

Methods

mfix :: (a -> ListenC o m a) -> ListenC o m a #

MonadFail m => MonadFail (ListenC o m) Source # 
Instance details

Defined in Control.Effect.Internal.Writer

Methods

fail :: String -> ListenC o m a #

Monad m => Applicative (ListenC o m) Source # 
Instance details

Defined in Control.Effect.Internal.Writer

Methods

pure :: a -> ListenC o m a #

(<*>) :: ListenC o m (a -> b) -> ListenC o m a -> ListenC o m b #

liftA2 :: (a -> b -> c) -> ListenC o m a -> ListenC o m b -> ListenC o m c #

(*>) :: ListenC o m a -> ListenC o m b -> ListenC o m b #

(<*) :: ListenC o m a -> ListenC o m b -> ListenC o m a #

MonadIO m => MonadIO (ListenC o m) Source # 
Instance details

Defined in Control.Effect.Internal.Writer

Methods

liftIO :: IO a -> ListenC o m a #

MonadPlus m => Alternative (ListenC o m) Source # 
Instance details

Defined in Control.Effect.Internal.Writer

Methods

empty :: ListenC o m a #

(<|>) :: ListenC o m a -> ListenC o m a -> ListenC o m a #

some :: ListenC o m a -> ListenC o m [a] #

many :: ListenC o m a -> ListenC o m [a] #

MonadPlus m => MonadPlus (ListenC o m) Source # 
Instance details

Defined in Control.Effect.Internal.Writer

Methods

mzero :: ListenC o m a #

mplus :: ListenC o m a -> ListenC o m a -> ListenC o m a #

MonadThrow m => MonadThrow (ListenC o m) Source # 
Instance details

Defined in Control.Effect.Internal.Writer

Methods

throwM :: Exception e => e -> ListenC o m a #

(Monoid o, MonadCatch m) => MonadCatch (ListenC o m) Source # 
Instance details

Defined in Control.Effect.Internal.Writer

Methods

catch :: Exception e => ListenC o m a -> (e -> ListenC o m a) -> ListenC o m a #

(Monoid o, MonadMask m) => MonadMask (ListenC o m) Source # 
Instance details

Defined in Control.Effect.Internal.Writer

Methods

mask :: ((forall a. ListenC o m a -> ListenC o m a) -> ListenC o m b) -> ListenC o m b #

uninterruptibleMask :: ((forall a. ListenC o m a -> ListenC o m a) -> ListenC o m b) -> ListenC o m b #

generalBracket :: ListenC o m a -> (a -> ExitCase b -> ListenC o m c) -> (a -> ListenC o m b) -> ListenC o m (b, c) #

(Carrier m, Monoid o, Threads (WriterT o) (Prims m)) => Carrier (ListenC o m) Source # 
Instance details

Defined in Control.Effect.Internal.Writer

Associated Types

type Derivs (ListenC o m) :: [Effect] Source #

type Prims (ListenC o m) :: [Effect] Source #

type StT (ListenC o) a Source # 
Instance details

Defined in Control.Effect.Internal.Writer

type StT (ListenC o) a = StT (TellC o) a
type Derivs (ListenC o m) Source # 
Instance details

Defined in Control.Effect.Internal.Writer

type Derivs (ListenC o m) = Listen o ': (Tell o ': Derivs m)
type Prims (ListenC o m) Source # 
Instance details

Defined in Control.Effect.Internal.Writer

type Prims (ListenC o m) = ListenPrim o ': Prims m
type StM (ListenC o m) a Source # 
Instance details

Defined in Control.Effect.Internal.Writer

type StM (ListenC o m) a = StM (TellC o m) a

newtype WriterC o m a Source #

Constructors

WriterC 

Fields

Instances

Instances details
MonadBase b m => MonadBase b (WriterC o m) Source # 
Instance details

Defined in Control.Effect.Internal.Writer

Methods

liftBase :: b α -> WriterC o m α #

(MonadBaseControl b m, Monoid o) => MonadBaseControl b (WriterC o m) Source # 
Instance details

Defined in Control.Effect.Internal.Writer

Associated Types

type StM (WriterC o m) a #

Methods

liftBaseWith :: (RunInBase (WriterC o m) b -> b a) -> WriterC o m a #

restoreM :: StM (WriterC o m) a -> WriterC o m a #

MonadTrans (WriterC o) Source # 
Instance details

Defined in Control.Effect.Internal.Writer

Methods

lift :: Monad m => m a -> WriterC o m a #

Monoid o => MonadTransControl (WriterC o) Source # 
Instance details

Defined in Control.Effect.Internal.Writer

Associated Types

type StT (WriterC o) a #

Methods

liftWith :: Monad m => (Run (WriterC o) -> m a) -> WriterC o m a #

restoreT :: Monad m => m (StT (WriterC o) a) -> WriterC o m a #

Monad m => Monad (WriterC o m) Source # 
Instance details

Defined in Control.Effect.Internal.Writer

Methods

(>>=) :: WriterC o m a -> (a -> WriterC o m b) -> WriterC o m b #

(>>) :: WriterC o m a -> WriterC o m b -> WriterC o m b #

return :: a -> WriterC o m a #

Functor m => Functor (WriterC o m) Source # 
Instance details

Defined in Control.Effect.Internal.Writer

Methods

fmap :: (a -> b) -> WriterC o m a -> WriterC o m b #

(<$) :: a -> WriterC o m b -> WriterC o m a #

MonadFix m => MonadFix (WriterC o m) Source # 
Instance details

Defined in Control.Effect.Internal.Writer

Methods

mfix :: (a -> WriterC o m a) -> WriterC o m a #

MonadFail m => MonadFail (WriterC o m) Source # 
Instance details

Defined in Control.Effect.Internal.Writer

Methods

fail :: String -> WriterC o m a #

Monad m => Applicative (WriterC o m) Source # 
Instance details

Defined in Control.Effect.Internal.Writer

Methods

pure :: a -> WriterC o m a #

(<*>) :: WriterC o m (a -> b) -> WriterC o m a -> WriterC o m b #

liftA2 :: (a -> b -> c) -> WriterC o m a -> WriterC o m b -> WriterC o m c #

(*>) :: WriterC o m a -> WriterC o m b -> WriterC o m b #

(<*) :: WriterC o m a -> WriterC o m b -> WriterC o m a #

MonadIO m => MonadIO (WriterC o m) Source # 
Instance details

Defined in Control.Effect.Internal.Writer

Methods

liftIO :: IO a -> WriterC o m a #

MonadPlus m => Alternative (WriterC o m) Source # 
Instance details

Defined in Control.Effect.Internal.Writer

Methods

empty :: WriterC o m a #

(<|>) :: WriterC o m a -> WriterC o m a -> WriterC o m a #

some :: WriterC o m a -> WriterC o m [a] #

many :: WriterC o m a -> WriterC o m [a] #

MonadPlus m => MonadPlus (WriterC o m) Source # 
Instance details

Defined in Control.Effect.Internal.Writer

Methods

mzero :: WriterC o m a #

mplus :: WriterC o m a -> WriterC o m a -> WriterC o m a #

MonadThrow m => MonadThrow (WriterC o m) Source # 
Instance details

Defined in Control.Effect.Internal.Writer

Methods

throwM :: Exception e => e -> WriterC o m a #

(Monoid o, MonadCatch m) => MonadCatch (WriterC o m) Source # 
Instance details

Defined in Control.Effect.Internal.Writer

Methods

catch :: Exception e => WriterC o m a -> (e -> WriterC o m a) -> WriterC o m a #

(Monoid o, MonadMask m) => MonadMask (WriterC o m) Source # 
Instance details

Defined in Control.Effect.Internal.Writer

Methods

mask :: ((forall a. WriterC o m a -> WriterC o m a) -> WriterC o m b) -> WriterC o m b #

uninterruptibleMask :: ((forall a. WriterC o m a -> WriterC o m a) -> WriterC o m b) -> WriterC o m b #

generalBracket :: WriterC o m a -> (a -> ExitCase b -> WriterC o m c) -> (a -> WriterC o m b) -> WriterC o m (b, c) #

(Carrier m, Monoid o, Threads (WriterT o) (Prims m)) => Carrier (WriterC o m) Source # 
Instance details

Defined in Control.Effect.Internal.Writer

Associated Types

type Derivs (WriterC o m) :: [Effect] Source #

type Prims (WriterC o m) :: [Effect] Source #

type StT (WriterC o) a Source # 
Instance details

Defined in Control.Effect.Internal.Writer

type StT (WriterC o) a = StT (TellC o) a
type Derivs (WriterC o m) Source # 
Instance details

Defined in Control.Effect.Internal.Writer

type Derivs (WriterC o m) = Pass o ': (Listen o ': (Tell o ': Derivs m))
type Prims (WriterC o m) Source # 
Instance details

Defined in Control.Effect.Internal.Writer

type Prims (WriterC o m) = WriterPrim o ': Prims m
type StM (WriterC o m) a Source # 
Instance details

Defined in Control.Effect.Internal.Writer

type StM (WriterC o m) a = StM (TellC o m) a

newtype TellLazyC o m a Source #

Constructors

TellLazyC 

Fields

Instances

Instances details
(Monoid o, MonadBase b m) => MonadBase b (TellLazyC o m) Source # 
Instance details

Defined in Control.Effect.Internal.Writer

Methods

liftBase :: b α -> TellLazyC o m α #

(Monoid o, MonadBaseControl b m) => MonadBaseControl b (TellLazyC o m) Source # 
Instance details

Defined in Control.Effect.Internal.Writer

Associated Types

type StM (TellLazyC o m) a #

Methods

liftBaseWith :: (RunInBase (TellLazyC o m) b -> b a) -> TellLazyC o m a #

restoreM :: StM (TellLazyC o m) a -> TellLazyC o m a #

Monoid o => MonadTrans (TellLazyC o) Source # 
Instance details

Defined in Control.Effect.Internal.Writer

Methods

lift :: Monad m => m a -> TellLazyC o m a #

Monoid o => MonadTransControl (TellLazyC o) Source # 
Instance details

Defined in Control.Effect.Internal.Writer

Associated Types

type StT (TellLazyC o) a #

Methods

liftWith :: Monad m => (Run (TellLazyC o) -> m a) -> TellLazyC o m a #

restoreT :: Monad m => m (StT (TellLazyC o) a) -> TellLazyC o m a #

(Monoid o, Monad m) => Monad (TellLazyC o m) Source # 
Instance details

Defined in Control.Effect.Internal.Writer

Methods

(>>=) :: TellLazyC o m a -> (a -> TellLazyC o m b) -> TellLazyC o m b #

(>>) :: TellLazyC o m a -> TellLazyC o m b -> TellLazyC o m b #

return :: a -> TellLazyC o m a #

Functor m => Functor (TellLazyC o m) Source # 
Instance details

Defined in Control.Effect.Internal.Writer

Methods

fmap :: (a -> b) -> TellLazyC o m a -> TellLazyC o m b #

(<$) :: a -> TellLazyC o m b -> TellLazyC o m a #

(Monoid o, MonadFix m) => MonadFix (TellLazyC o m) Source # 
Instance details

Defined in Control.Effect.Internal.Writer

Methods

mfix :: (a -> TellLazyC o m a) -> TellLazyC o m a #

(Monoid o, MonadFail m) => MonadFail (TellLazyC o m) Source # 
Instance details

Defined in Control.Effect.Internal.Writer

Methods

fail :: String -> TellLazyC o m a #

(Monoid o, Applicative m) => Applicative (TellLazyC o m) Source # 
Instance details

Defined in Control.Effect.Internal.Writer

Methods

pure :: a -> TellLazyC o m a #

(<*>) :: TellLazyC o m (a -> b) -> TellLazyC o m a -> TellLazyC o m b #

liftA2 :: (a -> b -> c) -> TellLazyC o m a -> TellLazyC o m b -> TellLazyC o m c #

(*>) :: TellLazyC o m a -> TellLazyC o m b -> TellLazyC o m b #

(<*) :: TellLazyC o m a -> TellLazyC o m b -> TellLazyC o m a #

(Monoid o, MonadIO m) => MonadIO (TellLazyC o m) Source # 
Instance details

Defined in Control.Effect.Internal.Writer

Methods

liftIO :: IO a -> TellLazyC o m a #

(Monoid o, Alternative m) => Alternative (TellLazyC o m) Source # 
Instance details

Defined in Control.Effect.Internal.Writer

Methods

empty :: TellLazyC o m a #

(<|>) :: TellLazyC o m a -> TellLazyC o m a -> TellLazyC o m a #

some :: TellLazyC o m a -> TellLazyC o m [a] #

many :: TellLazyC o m a -> TellLazyC o m [a] #

(Monoid o, MonadPlus m) => MonadPlus (TellLazyC o m) Source # 
Instance details

Defined in Control.Effect.Internal.Writer

Methods

mzero :: TellLazyC o m a #

mplus :: TellLazyC o m a -> TellLazyC o m a -> TellLazyC o m a #

(Monoid o, MonadThrow m) => MonadThrow (TellLazyC o m) Source # 
Instance details

Defined in Control.Effect.Internal.Writer

Methods

throwM :: Exception e => e -> TellLazyC o m a #

(Monoid o, MonadCatch m) => MonadCatch (TellLazyC o m) Source # 
Instance details

Defined in Control.Effect.Internal.Writer

Methods

catch :: Exception e => TellLazyC o m a -> (e -> TellLazyC o m a) -> TellLazyC o m a #

(Monoid o, MonadMask m) => MonadMask (TellLazyC o m) Source # 
Instance details

Defined in Control.Effect.Internal.Writer

Methods

mask :: ((forall a. TellLazyC o m a -> TellLazyC o m a) -> TellLazyC o m b) -> TellLazyC o m b #

uninterruptibleMask :: ((forall a. TellLazyC o m a -> TellLazyC o m a) -> TellLazyC o m b) -> TellLazyC o m b #

generalBracket :: TellLazyC o m a -> (a -> ExitCase b -> TellLazyC o m c) -> (a -> TellLazyC o m b) -> TellLazyC o m (b, c) #

(Monoid o, Carrier m, Threads (WriterT o) (Prims m)) => Carrier (TellLazyC o m) Source # 
Instance details

Defined in Control.Effect.Internal.Writer

Associated Types

type Derivs (TellLazyC o m) :: [Effect] Source #

type Prims (TellLazyC o m) :: [Effect] Source #

type StT (TellLazyC o) a Source # 
Instance details

Defined in Control.Effect.Internal.Writer

type StT (TellLazyC o) a = StT (WriterT o) a
type Derivs (TellLazyC o m) Source # 
Instance details

Defined in Control.Effect.Internal.Writer

type Derivs (TellLazyC o m) = Tell o ': Derivs m
type Prims (TellLazyC o m) Source # 
Instance details

Defined in Control.Effect.Internal.Writer

type Prims (TellLazyC o m) = Prims m
type StM (TellLazyC o m) a Source # 
Instance details

Defined in Control.Effect.Internal.Writer

type StM (TellLazyC o m) a = StM (WriterT o m) a

newtype ListenLazyC o m a Source #

Constructors

ListenLazyC 

Fields

Instances

Instances details
(Monoid o, MonadBase b m) => MonadBase b (ListenLazyC o m) Source # 
Instance details

Defined in Control.Effect.Internal.Writer

Methods

liftBase :: b α -> ListenLazyC o m α #

(Monoid o, MonadBaseControl b m) => MonadBaseControl b (ListenLazyC o m) Source # 
Instance details

Defined in Control.Effect.Internal.Writer

Associated Types

type StM (ListenLazyC o m) a #

Methods

liftBaseWith :: (RunInBase (ListenLazyC o m) b -> b a) -> ListenLazyC o m a #

restoreM :: StM (ListenLazyC o m) a -> ListenLazyC o m a #

Monoid o => MonadTrans (ListenLazyC o) Source # 
Instance details

Defined in Control.Effect.Internal.Writer

Methods

lift :: Monad m => m a -> ListenLazyC o m a #

Monoid o => MonadTransControl (ListenLazyC o) Source # 
Instance details

Defined in Control.Effect.Internal.Writer

Associated Types

type StT (ListenLazyC o) a #

Methods

liftWith :: Monad m => (Run (ListenLazyC o) -> m a) -> ListenLazyC o m a #

restoreT :: Monad m => m (StT (ListenLazyC o) a) -> ListenLazyC o m a #

(Monoid o, Monad m) => Monad (ListenLazyC o m) Source # 
Instance details

Defined in Control.Effect.Internal.Writer

Methods

(>>=) :: ListenLazyC o m a -> (a -> ListenLazyC o m b) -> ListenLazyC o m b #

(>>) :: ListenLazyC o m a -> ListenLazyC o m b -> ListenLazyC o m b #

return :: a -> ListenLazyC o m a #

Functor m => Functor (ListenLazyC o m) Source # 
Instance details

Defined in Control.Effect.Internal.Writer

Methods

fmap :: (a -> b) -> ListenLazyC o m a -> ListenLazyC o m b #

(<$) :: a -> ListenLazyC o m b -> ListenLazyC o m a #

(Monoid o, MonadFix m) => MonadFix (ListenLazyC o m) Source # 
Instance details

Defined in Control.Effect.Internal.Writer

Methods

mfix :: (a -> ListenLazyC o m a) -> ListenLazyC o m a #

(Monoid o, MonadFail m) => MonadFail (ListenLazyC o m) Source # 
Instance details

Defined in Control.Effect.Internal.Writer

Methods

fail :: String -> ListenLazyC o m a #

(Monoid o, Applicative m) => Applicative (ListenLazyC o m) Source # 
Instance details

Defined in Control.Effect.Internal.Writer

Methods

pure :: a -> ListenLazyC o m a #

(<*>) :: ListenLazyC o m (a -> b) -> ListenLazyC o m a -> ListenLazyC o m b #

liftA2 :: (a -> b -> c) -> ListenLazyC o m a -> ListenLazyC o m b -> ListenLazyC o m c #

(*>) :: ListenLazyC o m a -> ListenLazyC o m b -> ListenLazyC o m b #

(<*) :: ListenLazyC o m a -> ListenLazyC o m b -> ListenLazyC o m a #

(Monoid o, MonadIO m) => MonadIO (ListenLazyC o m) Source # 
Instance details

Defined in Control.Effect.Internal.Writer

Methods

liftIO :: IO a -> ListenLazyC o m a #

(Monoid o, Alternative m) => Alternative (ListenLazyC o m) Source # 
Instance details

Defined in Control.Effect.Internal.Writer

Methods

empty :: ListenLazyC o m a #

(<|>) :: ListenLazyC o m a -> ListenLazyC o m a -> ListenLazyC o m a #

some :: ListenLazyC o m a -> ListenLazyC o m [a] #

many :: ListenLazyC o m a -> ListenLazyC o m [a] #

(Monoid o, MonadPlus m) => MonadPlus (ListenLazyC o m) Source # 
Instance details

Defined in Control.Effect.Internal.Writer

Methods

mzero :: ListenLazyC o m a #

mplus :: ListenLazyC o m a -> ListenLazyC o m a -> ListenLazyC o m a #

(Monoid o, MonadThrow m) => MonadThrow (ListenLazyC o m) Source # 
Instance details

Defined in Control.Effect.Internal.Writer

Methods

throwM :: Exception e => e -> ListenLazyC o m a #

(Monoid o, MonadCatch m) => MonadCatch (ListenLazyC o m) Source # 
Instance details

Defined in Control.Effect.Internal.Writer

Methods

catch :: Exception e => ListenLazyC o m a -> (e -> ListenLazyC o m a) -> ListenLazyC o m a #

(Monoid o, MonadMask m) => MonadMask (ListenLazyC o m) Source # 
Instance details

Defined in Control.Effect.Internal.Writer

Methods

mask :: ((forall a. ListenLazyC o m a -> ListenLazyC o m a) -> ListenLazyC o m b) -> ListenLazyC o m b #

uninterruptibleMask :: ((forall a. ListenLazyC o m a -> ListenLazyC o m a) -> ListenLazyC o m b) -> ListenLazyC o m b #

generalBracket :: ListenLazyC o m a -> (a -> ExitCase b -> ListenLazyC o m c) -> (a -> ListenLazyC o m b) -> ListenLazyC o m (b, c) #

(Monoid o, Carrier m, Threads (WriterT o) (Prims m)) => Carrier (ListenLazyC o m) Source # 
Instance details

Defined in Control.Effect.Internal.Writer

Associated Types

type Derivs (ListenLazyC o m) :: [Effect] Source #

type Prims (ListenLazyC o m) :: [Effect] Source #

type StT (ListenLazyC o) a Source # 
Instance details

Defined in Control.Effect.Internal.Writer

type StT (ListenLazyC o) a = StT (WriterT o) a
type Derivs (ListenLazyC o m) Source # 
Instance details

Defined in Control.Effect.Internal.Writer

type Derivs (ListenLazyC o m) = Listen o ': (Tell o ': Derivs m)
type Prims (ListenLazyC o m) Source # 
Instance details

Defined in Control.Effect.Internal.Writer

type Prims (ListenLazyC o m) = ListenPrim o ': Prims m
type StM (ListenLazyC o m) a Source # 
Instance details

Defined in Control.Effect.Internal.Writer

type StM (ListenLazyC o m) a = StM (WriterT o m) a

newtype WriterLazyC o m a Source #

Constructors

WriterLazyC 

Fields

Instances

Instances details
(Monoid o, MonadBase b m) => MonadBase b (WriterLazyC o m) Source # 
Instance details

Defined in Control.Effect.Internal.Writer

Methods

liftBase :: b α -> WriterLazyC o m α #

(Monoid o, MonadBaseControl b m) => MonadBaseControl b (WriterLazyC o m) Source # 
Instance details

Defined in Control.Effect.Internal.Writer

Associated Types

type StM (WriterLazyC o m) a #

Methods

liftBaseWith :: (RunInBase (WriterLazyC o m) b -> b a) -> WriterLazyC o m a #

restoreM :: StM (WriterLazyC o m) a -> WriterLazyC o m a #

Monoid o => MonadTrans (WriterLazyC o) Source # 
Instance details

Defined in Control.Effect.Internal.Writer

Methods

lift :: Monad m => m a -> WriterLazyC o m a #

Monoid o => MonadTransControl (WriterLazyC o) Source # 
Instance details

Defined in Control.Effect.Internal.Writer

Associated Types

type StT (WriterLazyC o) a #

Methods

liftWith :: Monad m => (Run (WriterLazyC o) -> m a) -> WriterLazyC o m a #

restoreT :: Monad m => m (StT (WriterLazyC o) a) -> WriterLazyC o m a #

(Monoid o, Monad m) => Monad (WriterLazyC o m) Source # 
Instance details

Defined in Control.Effect.Internal.Writer

Methods

(>>=) :: WriterLazyC o m a -> (a -> WriterLazyC o m b) -> WriterLazyC o m b #

(>>) :: WriterLazyC o m a -> WriterLazyC o m b -> WriterLazyC o m b #

return :: a -> WriterLazyC o m a #

Functor m => Functor (WriterLazyC o m) Source # 
Instance details

Defined in Control.Effect.Internal.Writer

Methods

fmap :: (a -> b) -> WriterLazyC o m a -> WriterLazyC o m b #

(<$) :: a -> WriterLazyC o m b -> WriterLazyC o m a #

(Monoid o, MonadFix m) => MonadFix (WriterLazyC o m) Source # 
Instance details

Defined in Control.Effect.Internal.Writer

Methods

mfix :: (a -> WriterLazyC o m a) -> WriterLazyC o m a #

(Monoid o, MonadFail m) => MonadFail (WriterLazyC o m) Source # 
Instance details

Defined in Control.Effect.Internal.Writer

Methods

fail :: String -> WriterLazyC o m a #

(Monoid o, Applicative m) => Applicative (WriterLazyC o m) Source # 
Instance details

Defined in Control.Effect.Internal.Writer

Methods

pure :: a -> WriterLazyC o m a #

(<*>) :: WriterLazyC o m (a -> b) -> WriterLazyC o m a -> WriterLazyC o m b #

liftA2 :: (a -> b -> c) -> WriterLazyC o m a -> WriterLazyC o m b -> WriterLazyC o m c #

(*>) :: WriterLazyC o m a -> WriterLazyC o m b -> WriterLazyC o m b #

(<*) :: WriterLazyC o m a -> WriterLazyC o m b -> WriterLazyC o m a #

(Monoid o, MonadIO m) => MonadIO (WriterLazyC o m) Source # 
Instance details

Defined in Control.Effect.Internal.Writer

Methods

liftIO :: IO a -> WriterLazyC o m a #

(Monoid o, Alternative m) => Alternative (WriterLazyC o m) Source # 
Instance details

Defined in Control.Effect.Internal.Writer

Methods

empty :: WriterLazyC o m a #

(<|>) :: WriterLazyC o m a -> WriterLazyC o m a -> WriterLazyC o m a #

some :: WriterLazyC o m a -> WriterLazyC o m [a] #

many :: WriterLazyC o m a -> WriterLazyC o m [a] #

(Monoid o, MonadPlus m) => MonadPlus (WriterLazyC o m) Source # 
Instance details

Defined in Control.Effect.Internal.Writer

Methods

mzero :: WriterLazyC o m a #

mplus :: WriterLazyC o m a -> WriterLazyC o m a -> WriterLazyC o m a #

(Monoid o, MonadThrow m) => MonadThrow (WriterLazyC o m) Source # 
Instance details

Defined in Control.Effect.Internal.Writer

Methods

throwM :: Exception e => e -> WriterLazyC o m a #

(Monoid o, MonadCatch m) => MonadCatch (WriterLazyC o m) Source # 
Instance details

Defined in Control.Effect.Internal.Writer

Methods

catch :: Exception e => WriterLazyC o m a -> (e -> WriterLazyC o m a) -> WriterLazyC o m a #

(Monoid o, MonadMask m) => MonadMask (WriterLazyC o m) Source # 
Instance details

Defined in Control.Effect.Internal.Writer

Methods

mask :: ((forall a. WriterLazyC o m a -> WriterLazyC o m a) -> WriterLazyC o m b) -> WriterLazyC o m b #

uninterruptibleMask :: ((forall a. WriterLazyC o m a -> WriterLazyC o m a) -> WriterLazyC o m b) -> WriterLazyC o m b #

generalBracket :: WriterLazyC o m a -> (a -> ExitCase b -> WriterLazyC o m c) -> (a -> WriterLazyC o m b) -> WriterLazyC o m (b, c) #

(Monoid o, Carrier m, Threads (WriterT o) (Prims m)) => Carrier (WriterLazyC o m) Source # 
Instance details

Defined in Control.Effect.Internal.Writer

Associated Types

type Derivs (WriterLazyC o m) :: [Effect] Source #

type Prims (WriterLazyC o m) :: [Effect] Source #

type StT (WriterLazyC o) a Source # 
Instance details

Defined in Control.Effect.Internal.Writer

type StT (WriterLazyC o) a = StT (WriterT o) a
type Derivs (WriterLazyC o m) Source # 
Instance details

Defined in Control.Effect.Internal.Writer

type Derivs (WriterLazyC o m) = Pass o ': (Listen o ': (Tell o ': Derivs m))
type Prims (WriterLazyC o m) Source # 
Instance details

Defined in Control.Effect.Internal.Writer

type Prims (WriterLazyC o m) = WriterPrim o ': Prims m
type StM (WriterLazyC o m) a Source # 
Instance details

Defined in Control.Effect.Internal.Writer

type StM (WriterLazyC o m) a = StM (WriterT o m) a

class (forall o. Monoid o => Threads (WriterT o) p) => WriterThreads p Source #

WriterThreads accepts the following primitive effects:

Instances

Instances details
(forall o. Monoid o => Threads (WriterT o) p) => WriterThreads p Source # 
Instance details

Defined in Control.Effect.Internal.Writer

class (forall o. Monoid o => Threads (WriterT o) p) => WriterLazyThreads p Source #

WriterLazyThreads accepts the following primitive effects:

Instances

Instances details
(forall o. Monoid o => Threads (WriterT o) p) => WriterLazyThreads p Source # 
Instance details

Defined in Control.Effect.Internal.Writer