par-dual-0.1.0.0: ParDual class for Parallel <-> Sequential
Copyright(c) Gabriel Volpe 2020
LicenseApache-2.0
Maintainervolpegabriel@gmail.com
Stabilityexperimental
Safe HaskellSafe
LanguageHaskell2010

Control.ParDual.Class

Description

You can find here functions such as parMap2, parTraverse, parBitraverse, etc.

Synopsis

Documentation

class (Monad m, Applicative f) => ParDual f m | m -> f, f -> m where Source #

The ParDual class abstracts over Monads that have a dual Applicative instance that acts in a different useful way.

E.g., the duality between Either and Validation. As well as the duality between IO and Concurrently.

It can also be seen as an isomorphism defined at the class level.

Minimal complete definition

parallel, sequential

Methods

parallel :: forall a. m a -> f a Source #

A natural transformation from m to f

sequential :: forall a. f a -> m a Source #

A natural transformation from f to m

parMap2 :: m a0 -> m a1 -> (a0 -> a1 -> a) -> m a Source #

It is the analogue to using <$> and <*> for the dual Applicative of the current Monad, as defined by the relationship defined by the ParDual instance.

parMap3 :: m a0 -> m a1 -> m a2 -> (a0 -> a1 -> a2 -> a) -> m a Source #

It is the analogue to using <$> and <*> for the dual Applicative of the current Monad, as defined by the relationship defined by the ParDual instance.

parMap4 :: m a0 -> m a1 -> m a2 -> m a3 -> (a0 -> a1 -> a2 -> a3 -> a) -> m a Source #

It is the analogue to using <$> and <*> for the dual Applicative of the current Monad, as defined by the relationship defined by the ParDual instance.

parMap5 :: m a0 -> m a1 -> m a2 -> m a3 -> m a4 -> (a0 -> a1 -> a2 -> a3 -> a4 -> a) -> m a Source #

It is the analogue to using <$> and <*> for the dual Applicative of the current Monad, as defined by the relationship defined by the ParDual instance.

parMap6 :: m a0 -> m a1 -> m a2 -> m a3 -> m a4 -> m a5 -> (a0 -> a1 -> a2 -> a3 -> a4 -> a5 -> a) -> m a Source #

It is the analogue to using <$> and <*> for the dual Applicative of the current Monad, as defined by the relationship defined by the ParDual instance.

parTraverse :: Traversable t => (a -> m b) -> t a -> m (t b) Source #

Same as traverse, except it uses the dual Applicative of the current Monad, as defined by the ParDual relationship.

parTraverse_ :: Traversable t => (a -> m b) -> t a -> m () Source #

Same as traverse_, except it uses the dual Applicative of the current Monad, as defined by the ParDual relationship.

parSequence :: Traversable t => t (m a) -> m (t a) Source #

Same as sequence, except it uses the dual Applicative of the current Monad, as defined by the ParDual relationship.

parSequence_ :: Traversable t => t (m a) -> m () Source #

Same as sequence_, except it uses the dual Applicative of the current Monad, as defined by the ParDual relationship.

parProductR :: m a -> m b -> m b Source #

Same as *>, except it uses the dual Applicative of the current Monad, as defined by the ParDual relationship.

parProductL :: m a -> m b -> m a Source #

Same as <*, except it uses the dual Applicative of the current Monad, as defined by the ParDual relationship.

parBitraverse :: Bitraversable t => (a -> m c) -> (b -> m d) -> t a b -> m (t c d) Source #

Same as bitraverse, except it uses the dual Applicative of the current Monad, as defined by the ParDual relationship.

parBisequence :: Bitraversable t => t (m a) (m b) -> m (t a b) Source #

Same as bisequence, except it uses the dual Applicative of the current Monad, as defined by the ParDual relationship.

Instances

Instances details
ParDual Concurrently IO Source # 
Instance details

Defined in Control.ParDual.Class

Methods

parallel :: IO a -> Concurrently a Source #

sequential :: Concurrently a -> IO a Source #

parMap2 :: IO a0 -> IO a1 -> (a0 -> a1 -> a) -> IO a Source #

parMap3 :: IO a0 -> IO a1 -> IO a2 -> (a0 -> a1 -> a2 -> a) -> IO a Source #

parMap4 :: IO a0 -> IO a1 -> IO a2 -> IO a3 -> (a0 -> a1 -> a2 -> a3 -> a) -> IO a Source #

parMap5 :: IO a0 -> IO a1 -> IO a2 -> IO a3 -> IO a4 -> (a0 -> a1 -> a2 -> a3 -> a4 -> a) -> IO a Source #

parMap6 :: IO a0 -> IO a1 -> IO a2 -> IO a3 -> IO a4 -> IO a5 -> (a0 -> a1 -> a2 -> a3 -> a4 -> a5 -> a) -> IO a Source #

parTraverse :: Traversable t => (a -> IO b) -> t a -> IO (t b) Source #

parTraverse_ :: Traversable t => (a -> IO b) -> t a -> IO () Source #

parSequence :: Traversable t => t (IO a) -> IO (t a) Source #

parSequence_ :: Traversable t => t (IO a) -> IO () Source #

parProductR :: IO a -> IO b -> IO b Source #

parProductL :: IO a -> IO b -> IO a Source #

parBitraverse :: Bitraversable t => (a -> IO c) -> (b -> IO d) -> t a b -> IO (t c d) Source #

parBisequence :: Bitraversable t => t (IO a) (IO b) -> IO (t a b) Source #

ParDual ZipList [] Source # 
Instance details

Defined in Control.ParDual.Class

Methods

parallel :: [a] -> ZipList a Source #

sequential :: ZipList a -> [a] Source #

parMap2 :: [a0] -> [a1] -> (a0 -> a1 -> a) -> [a] Source #

parMap3 :: [a0] -> [a1] -> [a2] -> (a0 -> a1 -> a2 -> a) -> [a] Source #

parMap4 :: [a0] -> [a1] -> [a2] -> [a3] -> (a0 -> a1 -> a2 -> a3 -> a) -> [a] Source #

parMap5 :: [a0] -> [a1] -> [a2] -> [a3] -> [a4] -> (a0 -> a1 -> a2 -> a3 -> a4 -> a) -> [a] Source #

parMap6 :: [a0] -> [a1] -> [a2] -> [a3] -> [a4] -> [a5] -> (a0 -> a1 -> a2 -> a3 -> a4 -> a5 -> a) -> [a] Source #

parTraverse :: Traversable t => (a -> [b]) -> t a -> [t b] Source #

parTraverse_ :: Traversable t => (a -> [b]) -> t a -> [()] Source #

parSequence :: Traversable t => t [a] -> [t a] Source #

parSequence_ :: Traversable t => t [a] -> [()] Source #

parProductR :: [a] -> [b] -> [b] Source #

parProductL :: [a] -> [b] -> [a] Source #

parBitraverse :: Bitraversable t => (a -> [c]) -> (b -> [d]) -> t a b -> [t c d] Source #

parBisequence :: Bitraversable t => t [a] [b] -> [t a b] Source #

Semigroup e => ParDual (Validation e) (Either e) Source # 
Instance details

Defined in Control.ParDual.Class

Methods

parallel :: Either e a -> Validation e a Source #

sequential :: Validation e a -> Either e a Source #

parMap2 :: Either e a0 -> Either e a1 -> (a0 -> a1 -> a) -> Either e a Source #

parMap3 :: Either e a0 -> Either e a1 -> Either e a2 -> (a0 -> a1 -> a2 -> a) -> Either e a Source #

parMap4 :: Either e a0 -> Either e a1 -> Either e a2 -> Either e a3 -> (a0 -> a1 -> a2 -> a3 -> a) -> Either e a Source #

parMap5 :: Either e a0 -> Either e a1 -> Either e a2 -> Either e a3 -> Either e a4 -> (a0 -> a1 -> a2 -> a3 -> a4 -> a) -> Either e a Source #

parMap6 :: Either e a0 -> Either e a1 -> Either e a2 -> Either e a3 -> Either e a4 -> Either e a5 -> (a0 -> a1 -> a2 -> a3 -> a4 -> a5 -> a) -> Either e a Source #

parTraverse :: Traversable t => (a -> Either e b) -> t a -> Either e (t b) Source #

parTraverse_ :: Traversable t => (a -> Either e b) -> t a -> Either e () Source #

parSequence :: Traversable t => t (Either e a) -> Either e (t a) Source #

parSequence_ :: Traversable t => t (Either e a) -> Either e () Source #

parProductR :: Either e a -> Either e b -> Either e b Source #

parProductL :: Either e a -> Either e b -> Either e a Source #

parBitraverse :: Bitraversable t => (a -> Either e c) -> (b -> Either e d) -> t a b -> Either e (t c d) Source #

parBisequence :: Bitraversable t => t (Either e a) (Either e b) -> Either e (t a b) Source #