functor-monad-0.1.1.0: FFunctor: functors on (the usual) Functors
Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.Functor.Exp

Description

Exponentiation of a Functor by a Functor.

For reference:

Powers of polynomial monads by David Spivak https://topos.site/blog/2023/09/powers-of-polynomial-monads/

Documentation

newtype Exp1 f g a Source #

Constructors

Exp1 

Fields

  • unExp1 :: forall r. f r -> (a -> r) -> g r
     

Instances

Instances details
FFunctor (Exp1 f) Source # 
Instance details

Defined in Data.Functor.Exp

Methods

ffmap :: forall (g :: Type -> Type) (h :: Type -> Type) x. (Functor g, Functor h) => (g ~> h) -> Exp1 f g x -> Exp1 f h x Source #

Functor f => FMonad (Exp1 f) Source #

g ~ Exp1 Proxy g; Exp1 f (Exp1 f g) ~ Exp1 (f :*: f) g

Instance details

Defined in Data.Functor.Exp

Methods

fpure :: forall (g :: Type -> Type). Functor g => g ~> Exp1 f g Source #

fbind :: forall (g :: Type -> Type) (h :: Type -> Type) a. (Functor g, Functor h) => (g ~> Exp1 f h) -> Exp1 f g a -> Exp1 f h a Source #

Functor f => FStrong (Exp1 f) Source # 
Instance details

Defined in Data.Functor.Exp

Methods

fstrength :: forall (g :: Type -> Type) (h :: Type -> Type). Functor g => Day (Exp1 f g) h ~> Exp1 f (Day g h) Source #

mapCurried :: forall (g :: Type -> Type) (h :: Type -> Type). (Functor g, Functor h) => Curried g h ~> Curried (Exp1 f g) (Exp1 f h) Source #

(Comonad f, Monad g) => Alternative (Exp1 f g) Source # 
Instance details

Defined in Data.Functor.Exp

Methods

empty :: Exp1 f g a #

(<|>) :: Exp1 f g a -> Exp1 f g a -> Exp1 f g a #

some :: Exp1 f g a -> Exp1 f g [a] #

many :: Exp1 f g a -> Exp1 f g [a] #

(Functor f, Monad g) => Applicative (Exp1 f g) Source # 
Instance details

Defined in Data.Functor.Exp

Methods

pure :: a -> Exp1 f g a #

(<*>) :: Exp1 f g (a -> b) -> Exp1 f g a -> Exp1 f g b #

liftA2 :: (a -> b -> c) -> Exp1 f g a -> Exp1 f g b -> Exp1 f g c #

(*>) :: Exp1 f g a -> Exp1 f g b -> Exp1 f g b #

(<*) :: Exp1 f g a -> Exp1 f g b -> Exp1 f g a #

Functor (Exp1 f g) Source # 
Instance details

Defined in Data.Functor.Exp

Methods

fmap :: (a -> b) -> Exp1 f g a -> Exp1 f g b #

(<$) :: a -> Exp1 f g b -> Exp1 f g a #

(Functor f, Monad g) => Monad (Exp1 f g) Source # 
Instance details

Defined in Data.Functor.Exp

Methods

(>>=) :: Exp1 f g a -> (a -> Exp1 f g b) -> Exp1 f g b #

(>>) :: Exp1 f g a -> Exp1 f g b -> Exp1 f g b #

return :: a -> Exp1 f g a #

Functor f => Adjunction ((:*:) f) (Exp1 f) Source # 
Instance details

Defined in FFunctor.Adjunction

Methods

unit :: forall (g :: Type -> Type). Functor g => g ~> Exp1 f (f :*: g) Source #

counit :: forall (g :: Type -> Type). Functor g => (f :*: Exp1 f g) ~> g Source #

leftAdjunct :: forall (g :: Type -> Type) (h :: Type -> Type). (Functor g, Functor h) => ((f :*: g) ~> h) -> g ~> Exp1 f h Source #

rightAdjunct :: forall (g :: Type -> Type) (h :: Type -> Type). (Functor g, Functor h) => (g ~> Exp1 f h) -> (f :*: g) ~> h Source #

(Comonad f, Monad g) => Monoid (Exp1 f g a) Source #

Equivalent to Alt (Exp1 f g) a

Instance details

Defined in Data.Functor.Exp

Methods

mempty :: Exp1 f g a #

mappend :: Exp1 f g a -> Exp1 f g a -> Exp1 f g a #

mconcat :: [Exp1 f g a] -> Exp1 f g a #

(Comonad f, Monad g) => Semigroup (Exp1 f g a) Source #

Equivalent to Alt (Exp1 f g) a

Instance details

Defined in Data.Functor.Exp

Methods

(<>) :: Exp1 f g a -> Exp1 f g a -> Exp1 f g a #

sconcat :: NonEmpty (Exp1 f g a) -> Exp1 f g a #

stimes :: Integral b => b -> Exp1 f g a -> Exp1 f g a #

type (:^:) f g = Exp1 g f Source #

toExp1 :: forall f g h. Functor g => ((f :*: g) ~> h) -> g ~> Exp1 f h Source #

fromExp1 :: forall f g h. (g ~> Exp1 f h) -> (f :*: g) ~> h Source #

evalExp1 :: (f :*: Exp1 f g) ~> g Source #

coevalExp1 :: Functor g => g ~> Exp1 f (f :*: g) Source #

fromExp1' :: Functor f => Exp1 f g b -> f a -> g (Either a b) Source #

toExp1' :: Functor g => (forall a. f a -> g (Either a b)) -> Exp1 f g b Source #