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

Control.Effect.Conc

Description

Interface adapted from Control.Concurrent.Async

Synopsis

Effects

data Conc m a Source #

An effect for concurrent execution.

Instances

Instances details
EffNewtype Conc Source # 
Instance details

Defined in Control.Effect.Internal.Conc

Associated Types

type UnwrappedEff Conc :: Effect Source #

Methods

unwrapped :: forall (z :: Type -> Type) x. Conc z x -> UnwrappedEff Conc z x Source #

type UnwrappedEff Conc Source # 
Instance details

Defined in Control.Effect.Internal.Conc

data Async a #

An asynchronous action spawned by async or withAsync. Asynchronous actions are executed in a separate thread, and operations are provided for waiting for asynchronous actions to complete and obtaining their results (see e.g. wait).

Instances

Instances details
Functor Async 
Instance details

Defined in Control.Concurrent.Async

Methods

fmap :: (a -> b) -> Async a -> Async b #

(<$) :: a -> Async b -> Async a #

Eq (Async a) 
Instance details

Defined in Control.Concurrent.Async

Methods

(==) :: Async a -> Async a -> Bool #

(/=) :: Async a -> Async a -> Bool #

Ord (Async a) 
Instance details

Defined in Control.Concurrent.Async

Methods

compare :: Async a -> Async a -> Ordering #

(<) :: Async a -> Async a -> Bool #

(<=) :: Async a -> Async a -> Bool #

(>) :: Async a -> Async a -> Bool #

(>=) :: Async a -> Async a -> Bool #

max :: Async a -> Async a -> Async a #

min :: Async a -> Async a -> Async a #

Hashable (Async a) 
Instance details

Defined in Control.Concurrent.Async

Methods

hashWithSalt :: Int -> Async a -> Int #

hash :: Async a -> Int #

Interpretations

concToIO :: (Carrier m, MonadBaseControlPure IO m) => ConcToIOC m a -> m a Source #

Run a Conc effect if all effects used in the program -- past and future -- are eventually reduced to operations on IO.

Due to its very restrictive primitive effect and carrier constraint, concToIO can't be used together with most pure interpreters. For example, instead of runError, you must use errorToIO.

This poses a problem if you want to use some effect that doesn't have an interpreter compatible with concToIO -- like NonDet. In that case, you might still be able to use both effects in the same program by applying Split Interpretation to seperate their uses.

Derivs (ConcToIOC m) = Conc ': Derivs m
Prims  (ConcToIOC m) = Unlift IO ': Prims m

concToUnliftIO :: Eff (Unlift IO) m => ConcToUnliftIOC m a -> m a Source #

Transform a Conc effect into Unlift IO.

Key actions

async :: Eff Conc m => m a -> m (Async a) Source #

withAsync :: Eff Conc m => m a -> (Async a -> m b) -> m b Source #

wait :: Eff Conc m => Async a -> m a Source #

concurrently :: Eff Conc m => m a -> m b -> m (a, b) Source #

race :: Eff Conc m => m a -> m b -> m (Either a b) Source #

waitEither :: Eff Conc m => Async a -> Async b -> m (Either a b) Source #

waitBoth :: Eff Conc m => Async a -> Async b -> m (a, b) Source #

link :: Eff Conc m => Async a -> m () Source #

link2 :: Eff Conc m => Async a -> Async b -> m () Source #

waitAny :: Eff Conc m => [Async a] -> m (Async a, a) Source #

mapConcurrently :: (Traversable t, Eff Conc m) => (a -> m b) -> t a -> m (t b) Source #

forConcurrently :: (Traversable t, Eff Conc m) => t a -> (a -> m b) -> m (t b) Source #

Concurrently applicative

newtype Concurrently m a Source #

Constructors

Concurrently 

Fields

Instances

Instances details
Functor m => Functor (Concurrently m) Source # 
Instance details

Defined in Control.Effect.Conc

Methods

fmap :: (a -> b) -> Concurrently m a -> Concurrently m b #

(<$) :: a -> Concurrently m b -> Concurrently m a #

Eff Conc m => Applicative (Concurrently m) Source # 
Instance details

Defined in Control.Effect.Conc

Methods

pure :: a -> Concurrently m a #

(<*>) :: Concurrently m (a -> b) -> Concurrently m a -> Concurrently m b #

liftA2 :: (a -> b -> c) -> Concurrently m a -> Concurrently m b -> Concurrently m c #

(*>) :: Concurrently m a -> Concurrently m b -> Concurrently m b #

(<*) :: Concurrently m a -> Concurrently m b -> Concurrently m a #

Eff Conc m => Alternative (Concurrently m) Source # 
Instance details

Defined in Control.Effect.Conc

Methods

empty :: Concurrently m a #

(<|>) :: Concurrently m a -> Concurrently m a -> Concurrently m a #

some :: Concurrently m a -> Concurrently m [a] #

many :: Concurrently m a -> Concurrently m [a] #

(Eff Conc m, Semigroup a) => Semigroup (Concurrently m a) Source # 
Instance details

Defined in Control.Effect.Conc

Methods

(<>) :: Concurrently m a -> Concurrently m a -> Concurrently m a #

sconcat :: NonEmpty (Concurrently m a) -> Concurrently m a #

stimes :: Integral b => b -> Concurrently m a -> Concurrently m a #

(Eff Conc m, Monoid a) => Monoid (Concurrently m a) Source # 
Instance details

Defined in Control.Effect.Conc

Other actions

asyncBound :: Eff Conc m => m a -> m (Async a) Source #

asyncOn :: Eff Conc m => Int -> m a -> m (Async a) Source #

asyncWithUnmask :: Eff Conc m => ((forall x. m x -> m x) -> m a) -> m (Async a) Source #

asyncOnWithUnmask :: Eff Conc m => Int -> ((forall x. m x -> m x) -> m a) -> m (Async a) Source #

withAsyncBound :: Eff Conc m => m a -> (Async a -> m b) -> m b Source #

withAsyncWithUnmask :: Eff Conc m => ((forall x. m x -> m x) -> m a) -> (Async a -> m b) -> m b Source #

withAsyncOnWithUnmask :: Eff Conc m => Int -> ((forall x. m x -> m x) -> m a) -> (Async a -> m b) -> m b Source #

cancel :: Eff Conc m => Async a -> m () Source #

cancelWith :: Eff Conc m => (Exception e, Eff Conc m) => Async a -> e -> m () Source #

waitAnyCancel :: Eff Conc m => [Async a] -> m (Async a, a) Source #

waitEitherCancel :: Eff Conc m => Async a -> Async b -> m (Either a b) Source #

waitEither_ :: Eff Conc m => Async a -> Async b -> m () Source #

linkOnly :: Eff Conc m => (SomeException -> Bool) -> Async a -> m () Source #

link2Only :: Eff Conc m => (SomeException -> Bool) -> Async a -> Async b -> m () Source #

race_ :: Eff Conc m => m a -> m b -> m () Source #

concurrently_ :: Eff Conc m => m a -> m b -> m () Source #

mapConcurrently_ :: (Foldable t, Eff Conc m) => (a -> m b) -> t a -> m () Source #

forConcurrently_ :: (Foldable t, Eff Conc m) => t a -> (a -> m b) -> m () Source #

replicateConcurrently :: Eff Conc m => Int -> m a -> m [a] Source #

replicateConcurrently_ :: Eff Conc m => Int -> m a -> m () Source #

Re-exports from Control.Concurrent.Async

asyncThreadId :: Async a -> ThreadId #

Returns the ThreadId of the thread running the given Async.

data AsyncCancelled #

The exception thrown by cancel to terminate a thread.

Constructors

AsyncCancelled 

waitAnySTM :: [Async a] -> STM (Async a, a) #

A version of waitAny that can be used inside an STM transaction.

Since: async-2.1.0

waitAnyCatchSTM :: [Async a] -> STM (Async a, Either SomeException a) #

A version of waitAnyCatch that can be used inside an STM transaction.

Since: async-2.1.0

waitEitherSTM :: Async a -> Async b -> STM (Either a b) #

A version of waitEither that can be used inside an STM transaction.

Since: async-2.1.0

waitEitherCatchSTM :: Async a -> Async b -> STM (Either (Either SomeException a) (Either SomeException b)) #

A version of waitEitherCatch that can be used inside an STM transaction.

Since: async-2.1.0

waitEitherSTM_ :: Async a -> Async b -> STM () #

A version of waitEither_ that can be used inside an STM transaction.

Since: async-2.1.0

waitBothSTM :: Async a -> Async b -> STM (a, b) #

A version of waitBoth that can be used inside an STM transaction.

Since: async-2.1.0

compareAsyncs :: Async a -> Async b -> Ordering #

Compare two Asyncs that may have different types by their ThreadId.

Carriers

data ConcToIOC m a Source #

Instances

Instances details
MonadTrans ConcToIOC Source # 
Instance details

Defined in Control.Effect.Internal.Conc

Methods

lift :: Monad m => m a -> ConcToIOC m a #

MonadBase b m => MonadBase b (ConcToIOC m) Source # 
Instance details

Defined in Control.Effect.Internal.Conc

Methods

liftBase :: b α -> ConcToIOC m α #

MonadBaseControl b m => MonadBaseControl b (ConcToIOC m) Source # 
Instance details

Defined in Control.Effect.Internal.Conc

Associated Types

type StM (ConcToIOC m) a #

Methods

liftBaseWith :: (RunInBase (ConcToIOC m) b -> b a) -> ConcToIOC m a #

restoreM :: StM (ConcToIOC m) a -> ConcToIOC m a #

Monad m => Monad (ConcToIOC m) Source # 
Instance details

Defined in Control.Effect.Internal.Conc

Methods

(>>=) :: ConcToIOC m a -> (a -> ConcToIOC m b) -> ConcToIOC m b #

(>>) :: ConcToIOC m a -> ConcToIOC m b -> ConcToIOC m b #

return :: a -> ConcToIOC m a #

Functor m => Functor (ConcToIOC m) Source # 
Instance details

Defined in Control.Effect.Internal.Conc

Methods

fmap :: (a -> b) -> ConcToIOC m a -> ConcToIOC m b #

(<$) :: a -> ConcToIOC m b -> ConcToIOC m a #

MonadFix m => MonadFix (ConcToIOC m) Source # 
Instance details

Defined in Control.Effect.Internal.Conc

Methods

mfix :: (a -> ConcToIOC m a) -> ConcToIOC m a #

MonadFail m => MonadFail (ConcToIOC m) Source # 
Instance details

Defined in Control.Effect.Internal.Conc

Methods

fail :: String -> ConcToIOC m a #

Applicative m => Applicative (ConcToIOC m) Source # 
Instance details

Defined in Control.Effect.Internal.Conc

Methods

pure :: a -> ConcToIOC m a #

(<*>) :: ConcToIOC m (a -> b) -> ConcToIOC m a -> ConcToIOC m b #

liftA2 :: (a -> b -> c) -> ConcToIOC m a -> ConcToIOC m b -> ConcToIOC m c #

(*>) :: ConcToIOC m a -> ConcToIOC m b -> ConcToIOC m b #

(<*) :: ConcToIOC m a -> ConcToIOC m b -> ConcToIOC m a #

MonadIO m => MonadIO (ConcToIOC m) Source # 
Instance details

Defined in Control.Effect.Internal.Conc

Methods

liftIO :: IO a -> ConcToIOC m a #

Alternative m => Alternative (ConcToIOC m) Source # 
Instance details

Defined in Control.Effect.Internal.Conc

Methods

empty :: ConcToIOC m a #

(<|>) :: ConcToIOC m a -> ConcToIOC m a -> ConcToIOC m a #

some :: ConcToIOC m a -> ConcToIOC m [a] #

many :: ConcToIOC m a -> ConcToIOC m [a] #

MonadPlus m => MonadPlus (ConcToIOC m) Source # 
Instance details

Defined in Control.Effect.Internal.Conc

Methods

mzero :: ConcToIOC m a #

mplus :: ConcToIOC m a -> ConcToIOC m a -> ConcToIOC m a #

MonadThrow m => MonadThrow (ConcToIOC m) Source # 
Instance details

Defined in Control.Effect.Internal.Conc

Methods

throwM :: Exception e => e -> ConcToIOC m a #

MonadCatch m => MonadCatch (ConcToIOC m) Source # 
Instance details

Defined in Control.Effect.Internal.Conc

Methods

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

MonadMask m => MonadMask (ConcToIOC m) Source # 
Instance details

Defined in Control.Effect.Internal.Conc

Methods

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

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

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

(Carrier m, MonadBaseControlPure IO m) => Carrier (ConcToIOC m) Source # 
Instance details

Defined in Control.Effect.Internal.Conc

Associated Types

type Derivs (ConcToIOC m) :: [Effect] Source #

type Prims (ConcToIOC m) :: [Effect] Source #

type Derivs (ConcToIOC m) Source # 
Instance details

Defined in Control.Effect.Internal.Conc

type Prims (ConcToIOC m) Source # 
Instance details

Defined in Control.Effect.Internal.Conc

type StM (ConcToIOC m) a Source # 
Instance details

Defined in Control.Effect.Internal.Conc