Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Monads in the cateogory of Functor
s.
Documentation
FMonad
class FFunctor ff => FMonad ff where Source #
FMonad
is to FFunctor
what Monad
is to Functor
.
|
| |
---|---|---|
Superclass |
|
|
Features |
return = pure
:: a -> m a
|
fpure
:: (Functor g)
=> g ~> mm g
|
(=<<)
:: (a -> m b)
-> (m a -> m b)
|
fbind
:: (Functor g, Functor h)
=> (g ~> mm h)
-> (mm g ~> mm h)
|
fpure :: Functor g => g ~> ff g Source #
fbind :: (Functor g, Functor h) => (g ~> ff h) -> ff g a -> ff h a Source #
Instances
FMonad laws
Laws
Like Monad
, there is a set of laws which every instance of FMonad
should satisfy.
- fpure is natural in g
Let g, h
be arbitrary Functor
s. For any natural transformation n :: g ~> h
,
ffmap n . fpure = fpure . n
- fbind is natural in g,h
Let g, g', h, h'
be arbitrary Functor
s. For all natural transformations
k :: g ~> ff h
, nat_g :: g' ~> g
, and nat_h :: h ~> h'
, the following holds.
fbind (ffmap nat_h . k . nat_g) = ffmap nat_h . fbind k . ffmap nat_g
- Left unit
fbind k . fpure = k
- Right unit
fbind fpure = id
- Associativity
fbind k . fbind j = fbind (fbind k . j)
Laws (in terms of fjoin
)
Alternatively, FMonad
laws can be stated using fjoin
instead.
- fpure is natural in g
For all Functor g
, Functor h
, and n :: g ~> h
,
ffmap n . fpure = fpure . n
- fjoin is natural in g
For all Functor g
, Functor h
, and n :: g ~> h
,
ffmap n . fjoin = fjoin . ffmap (ffmap n)
- Left unit
fjoin . fpure = id
- Right unit
fjoin . ffmap fpure = id
- Associativity
fjoin . fjoin = fjoin . ffmap fjoin
Re-export
class (forall g. Functor g => Functor (ff g)) => FFunctor ff where Source #
Endofunctors on the category of Functor
s.
|
| |
---|---|---|
Takes | A type a | A Functor g |
Makes | A type f a | A Functor (ff g) |
Feature |
fmap
:: (a -> b) -> f a -> f b
|
ffmap
:: (Functor g, Functor h)
=> (g ~> h) -> (ff g ~> ff h)
|
FFunctor laws:
- Identity
ffmap id = id
- Composition
ffmap f . ffmap g = ffmap (f . g)
Examples
This is the FFunctor
instance of
.
Just like the Sum
ffmap
from Functor (Either a)
instance which applies a function to the "Right" value,
ffmap
applies gh :: g ~> h
to the InR (g a)
value.
data Sum f g a = InL (f a) | InR (g a) instance (Functor f) => FFunctor (Sum f) where ffmap gh fgx = case fgx of InL fx -> InL fx InR gx -> InR (gh gx)
Like Sum f
, some instances of FFunctor
are modified Functor
s in such a way that
its parameter is swapped for g a
.
But not every instance of FFunctor
is like this. The following data type Foo g a
is a FFunctor
which uses a Functor g
and a type parameter a
separately.
data Foo g a = Foo (String -> a) (g String) instance Functor (Foo g) where fmap :: (a -> b) -> Foo g a -> Foo g b fmap f (Foo strToA gStr) = Foo (f . strToA) gStr instance FFunctor Foo where ffmap :: (g ~> h) -> Foo g a -> Foo h a ffmap gh (Foo strToA gStr) = Foo strToA (gh gStr)
An FFunctor
instance can use its Functor
parameter nested. The following Bar g a
example uses
g
nested twice.
newtype Bar g a = Bar (g (g a)) instance Functor g => Functor (Bar g) where fmap f (Bar gga) = Bar $ fmap (fmap f gga) instance FFunctor Bar where ffmap gh (Bar gga) = Bar $ fmap gh (gh gga)
Non-example
has the right kind to be an ContT
rFFunctor
, that is,
(Type -> Type) -> Type -> Type
. But there can be no instances of FFunctor (ContT r)
,
because ContT r m
uses m
in negative position.
newtype ContT r m a = ContT { runContT :: (a -> m r) -> m r -- ^ ^ positive position -- | negative position }