-- 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.7.3 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 class Functor f => FunctorApply f (<.>) :: FunctorApply f => f (a -> b) -> f a -> f b (.>) :: FunctorApply f => f a -> f b -> f b (<.) :: FunctorApply f => f a -> f b -> f a -- | A variant of <.> with the arguments reversed. (<..>) :: FunctorApply w => w a -> w (a -> b) -> w b -- | Lift a binary function into a comonad with zipping liftF2 :: FunctorApply w => (a -> b -> c) -> w a -> w b -> w c -- | Lift a ternary function into a comonad with zipping liftF3 :: FunctorApply w => (a -> b -> c -> d) -> w a -> w b -> w c -> w d -- | Wrap an Applicative to be used as a member of -- FunctorApply newtype WrappedApplicative f a WrappedApplicative :: f a -> WrappedApplicative f a unwrapApplicative :: WrappedApplicative f a -> f a -- | Transform a FunctorApply 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 instance FunctorApply (Cokleisli w a) instance Comonad f => Comonad (MaybeApply f) instance FunctorApply f => Applicative (MaybeApply f) instance FunctorApply f => FunctorApply (MaybeApply f) instance Functor f => Functor (MaybeApply f) instance Applicative f => Applicative (WrappedApplicative f) instance Applicative f => FunctorApply (WrappedApplicative f) instance Functor f => Functor (WrappedApplicative f) instance FunctorApply Tree instance FunctorApply Seq instance FunctorApply IntMap instance Ord k => FunctorApply (Map k) instance Arrow a => FunctorApply (WrappedArrow a b) instance Monad m => FunctorApply (WrappedMonad m) instance FunctorApply w => FunctorApply (IdentityT w) instance FunctorApply Identity instance FunctorApply Maybe instance FunctorApply IO instance FunctorApply [] instance FunctorApply ZipList instance FunctorApply ((->) m) instance Semigroup m => FunctorApply (Const m) instance Semigroup m => FunctorApply ((,) m) 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, FunctorApply f) => (a -> f b) -> t a -> f () for1_ :: (Foldable1 t, FunctorApply f) => t a -> (a -> f b) -> f () sequenceA1_ :: (Foldable1 t, FunctorApply 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 FunctorApply f => Semigroup (Act f a) module Data.Semigroup.Traversable class (Foldable1 t, Traversable t) => Traversable1 t traverse1 :: (Traversable1 t, FunctorApply f) => (a -> f b) -> t a -> f (t b) sequence1 :: (Traversable1 t, FunctorApply 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 FunctorApply that: -- --
--   pure (a b) = pure a <.> pure b
--   
class (Comonad w, FunctorApply 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 => ComonadApply ((->) m) instance (Monoid m, Semigroup m) => ComonadApply ((,) m)