-- Hoogle documentation, generated by Haddock -- See Hoogle, http://www.haskell.org/hoogle/ -- | Strong lax semimonoidal endofunctors (Applicative sans pure) -- -- Strong lax semimonoidal endofunctors (Applicative sans pure) @package functor-apply @version 0.9.1 -- | NB: The definitions exported through Data.Functor.Apply need to -- be included here because otherwise the instances for the transformers -- package have orphaned heads. module Data.Functor.Bind -- | The Functor class is used for types that can be mapped over. -- Instances of Functor should satisfy the following laws: -- --
--   fmap id  ==  id
--   fmap (f . g)  ==  fmap f . fmap g
--   
-- -- The instances of Functor for lists, Data.Maybe.Maybe -- and System.IO.IO satisfy these laws. class Functor f :: (* -> *) fmap :: Functor f => (a -> b) -> f a -> f b (<$) :: Functor f => a -> f b -> f a -- | An infix synonym for fmap. (<$>) :: Functor f => (a -> b) -> f a -> f b -- | TODO: move into Data.Functor ($>) :: Functor f => f a -> b -> f b -- | A strong lax semi-monoidal endofunctor. This is equivalent to an -- Applicative without pure. -- -- Laws: -- --
--   associative composition: (.) <$> u <.> v <.> w = u <.> (v <.> w)
--   
class Functor f => Apply f (<.>) :: Apply f => f (a -> b) -> f a -> f b (.>) :: Apply f => f a -> f b -> f b (<.) :: Apply f => f a -> f b -> f a -- | A variant of <.> with the arguments reversed. (<..>) :: Apply w => w a -> w (a -> b) -> w b -- | Lift a binary function into a comonad with zipping liftF2 :: Apply w => (a -> b -> c) -> w a -> w b -> w c -- | Lift a ternary function into a comonad with zipping liftF3 :: Apply w => (a -> b -> c -> d) -> w a -> w b -> w c -> w d -- | Wrap an Applicative to be used as a member of Apply newtype WrappedApplicative f a WrapApplicative :: f a -> WrappedApplicative f a unwrapApplicative :: WrappedApplicative f a -> f a -- | Transform a Apply into an Applicative by adding a unit. newtype MaybeApply f a MaybeApply :: Either (f a) a -> MaybeApply f a runMaybeApply :: MaybeApply f a -> Either (f a) a -- | A Monad sans return. -- -- Minimal definition: Either join or >>- -- -- If defining both, then the following laws (the default definitions) -- must hold: -- --
--   join = (>>- id)
--   m >>- f = join (fmap f m)
--   
-- -- Laws: -- --
--   induced definition of <.>: f <.> x = f >>- (<$> x)
--   
-- -- Finally, there are two associativity conditions: -- --
--   associativity of (>>-):    (m >>- f) >>- g == m >>- (\x -> f x >>- g)
--   associativity of join:     join . join = join . fmap join
--   
-- -- These can both be seen as special cases of the constraint that -- --
--   associativity of (->-): (f ->- g) ->- h = f ->- (g ->- h)
--   
class Apply m => Bind m (>>-) :: Bind m => m a -> (a -> m b) -> m b join :: Bind m => m (m a) -> m a (-<<) :: Bind m => (a -> m b) -> m a -> m b (-<-) :: Bind m => (b -> m c) -> (a -> m b) -> a -> m c (->-) :: Bind m => (a -> m b) -> (b -> m c) -> a -> m c apDefault :: Bind f => f (a -> b) -> f a -> f b returning :: Functor f => f a -> (a -> b) -> f b instance Bind Tree instance Bind Seq instance Bind IntMap instance Ord k => Bind (Map k) instance (Bind m, Semigroup w) => Bind (RWST r w s m) instance (Bind m, Semigroup w) => Bind (RWST r w s m) instance Bind m => Bind (StateT s m) instance Bind m => Bind (StateT s m) instance (Bind m, Semigroup w) => Bind (WriterT w m) instance (Bind m, Semigroup w) => Bind (WriterT w m) instance Bind m => Bind (ReaderT e m) instance (Apply m, Monad m) => Bind (ErrorT e m) instance (Bind m, Monad m) => Bind (ListT m) instance (Bind m, Monad m) => Bind (MaybeT m) instance Monad m => Bind (WrappedMonad m) instance Bind m => Bind (IdentityT m) instance Bind Identity instance Bind Option instance Bind Maybe instance Bind IO instance Bind [] instance Bind ((->) m) instance Bind (Either a) instance Semigroup m => Bind ((,) m) instance Apply (Cokleisli w a) instance Comonad f => Comonad (MaybeApply f) instance Extend f => Extend (MaybeApply f) instance Apply f => Applicative (MaybeApply f) instance Apply f => Apply (MaybeApply f) instance Functor f => Functor (MaybeApply f) instance Applicative f => Applicative (WrappedApplicative f) instance Applicative f => Apply (WrappedApplicative f) instance Functor f => Functor (WrappedApplicative f) instance (Bind m, Semigroup w) => Apply (RWST r w s m) instance (Bind m, Semigroup w) => Apply (RWST r w s m) instance Bind m => Apply (StateT s m) instance Bind m => Apply (StateT s m) instance (Apply m, Semigroup w) => Apply (WriterT w m) instance (Apply m, Semigroup w) => Apply (WriterT w m) instance Apply m => Apply (ListT m) instance Apply m => Apply (ReaderT e m) instance Apply m => Apply (ErrorT e m) instance Apply m => Apply (MaybeT m) instance Apply Tree instance Apply Seq instance Apply IntMap instance Ord k => Apply (Map k) instance Arrow a => Apply (WrappedArrow a b) instance Monad m => Apply (WrappedMonad m) instance Apply w => Apply (IdentityT w) instance Apply Identity instance Apply Option instance Apply Maybe instance Apply IO instance Apply [] instance Apply ZipList instance Apply ((->) m) instance Semigroup m => Apply (Const m) instance Apply (Either a) instance Semigroup m => Apply ((,) m) instance (Apply f, Apply g) => Apply (Product f g) instance (Apply f, Apply g) => Apply (Compose f g) module Data.Functor.Apply -- | The Functor class is used for types that can be mapped over. -- Instances of Functor should satisfy the following laws: -- --
--   fmap id  ==  id
--   fmap (f . g)  ==  fmap f . fmap g
--   
-- -- The instances of Functor for lists, Data.Maybe.Maybe -- and System.IO.IO satisfy these laws. class Functor f :: (* -> *) fmap :: Functor f => (a -> b) -> f a -> f b (<$) :: Functor f => a -> f b -> f a -- | An infix synonym for fmap. (<$>) :: Functor f => (a -> b) -> f a -> f b -- | TODO: move into Data.Functor ($>) :: Functor f => f a -> b -> f b -- | A strong lax semi-monoidal endofunctor. This is equivalent to an -- Applicative without pure. -- -- Laws: -- --
--   associative composition: (.) <$> u <.> v <.> w = u <.> (v <.> w)
--   
class Functor f => Apply f (<.>) :: Apply f => f (a -> b) -> f a -> f b (.>) :: Apply f => f a -> f b -> f b (<.) :: Apply f => f a -> f b -> f a -- | A variant of <.> with the arguments reversed. (<..>) :: Apply w => w a -> w (a -> b) -> w b -- | Lift a binary function into a comonad with zipping liftF2 :: Apply w => (a -> b -> c) -> w a -> w b -> w c -- | Lift a ternary function into a comonad with zipping liftF3 :: Apply w => (a -> b -> c -> d) -> w a -> w b -> w c -> w d -- | Wrap an Applicative to be used as a member of Apply newtype WrappedApplicative f a WrapApplicative :: f a -> WrappedApplicative f a unwrapApplicative :: WrappedApplicative f a -> f a -- | Transform a Apply into an Applicative by adding a unit. newtype MaybeApply f a MaybeApply :: Either (f a) a -> MaybeApply f a runMaybeApply :: MaybeApply f a -> Either (f a) a module Data.Semigroup.Foldable class Foldable t => Foldable1 t fold1 :: (Foldable1 t, Semigroup m) => t m -> m foldMap1 :: (Foldable1 t, Semigroup m) => (a -> m) -> t a -> m traverse1_ :: (Foldable1 t, Apply f) => (a -> f b) -> t a -> f () for1_ :: (Foldable1 t, Apply f) => t a -> (a -> f b) -> f () sequenceA1_ :: (Foldable1 t, Apply f) => t (f a) -> f () -- | Usable default for foldMap, but only if you define foldMap1 yourself foldMapDefault1 :: (Foldable1 t, Monoid m) => (a -> m) -> t a -> m instance Functor f => Functor (Act f) instance Apply f => Semigroup (Act f a) module Data.Semigroup.Traversable class (Foldable1 t, Traversable t) => Traversable1 t traverse1 :: (Traversable1 t, Apply f) => (a -> f b) -> t a -> f (t b) sequence1 :: (Traversable1 t, Apply f) => t (f b) -> f (t b) foldMap1Default :: (Traversable1 f, Semigroup m) => (a -> m) -> f a -> m -- | A Comonad is the categorical dual of a Monad. module Control.Comonad.Apply -- | A strong lax symmetric semi-monoidal comonad. As such, an instance of -- ComonadApply is required to satisfy: -- --
--   extract (a <.> b) = extract a $ extract b
--   
-- -- This class is based on ComonadZip from "The Essence of Dataflow -- Programming" by Tarmo Uustalu and Varmo Vene, but adapted to fit the -- programming style of Control.Applicative. Applicative can be -- seen as a similar law over and above Apply that: -- --
--   pure (a $ b) = pure a <.> pure b
--   
class (Comonad w, Apply w) => ComonadApply w -- | Lift a binary function into a comonad with zipping liftW2 :: ComonadApply w => (a -> b -> c) -> w a -> w b -> w c -- | Lift a ternary function into a comonad with zipping liftW3 :: ComonadApply w => (a -> b -> c -> d) -> w a -> w b -> w c -> w d instance ComonadApply w => ArrowLoop (Cokleisli w) instance ComonadApply w => ComonadApply (MaybeApply w) instance ComonadApply w => ComonadApply (IdentityT w) instance ComonadApply Identity instance (Monoid m, Semigroup m) => ComonadApply ((->) m) instance (Monoid m, Semigroup m) => ComonadApply ((,) m) module Data.Functor.Alt -- | Laws: -- --
--   <!> is associative:             (a <!> b) <!> c = a <!> (b <!> c)
--   <.> right-distributes over <!>: (a <!> b) <.> c = (a <.> c) <!> (b <.> c)
--   <$> left-distributes over <!>:  f <$> (a <!> b) = (f <$> a) <!> (f <$> b)
--   
class Apply f => Alt f () :: Alt f => f a -> f a -> f a instance Alternative f => Alt (WrappedApplicative f) instance Alt Seq instance Alt IntMap instance Ord k => Alt (Map k) instance ArrowPlus a => Alt (WrappedArrow a b) instance MonadPlus m => Alt (WrappedMonad m) instance Alt Option instance Alt Maybe instance Alt [] instance Alt IO instance Alt (Either a) module Control.Applicative.Alt class (Applicative f, Alt f) => ApplicativeAlt f some :: ApplicativeAlt f => f a -> f [a] many :: ApplicativeAlt f => f a -> f [a] instance Alternative f => ApplicativeAlt (WrappedApplicative f) instance ArrowPlus a => ApplicativeAlt (WrappedArrow a b) instance MonadPlus m => ApplicativeAlt (WrappedMonad m) instance ApplicativeAlt Option instance ApplicativeAlt Maybe instance ApplicativeAlt IO instance ApplicativeAlt []