functor-combinators-0.1.0.0: Tools for functor combinator-based program design

Copyright(c) Justin Le 2019
LicenseBSD3
Maintainerjustin@jle.im
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

Data.HBifunctor.Tensor

Contents

Description

This module provides tools for working with binary functor combinators.

Data.Functor.HFunctor deals with single functor combinators (transforming a single functor). This module provides tools for working with combinators that combine and mix two functors "together".

The binary analog of HFunctor is HBifunctor: we can map a structure-transforming function over both of the transformed functors.

The binary analog of Interpret is Monoidal (and Tensor). If your combinator is an instance of Monoidal, it means that you can "squish" both arguments together into an Interpret. For example:

toMF :: (f :*: f) a -> ListF f a
toMF :: Comp f f a -> Free f a
toMF :: Day f f a -> Ap f a
Synopsis

Tensor

class Associative t => Tensor t where Source #

An Associative HBifunctor can be a Tensor if there is some identity i where t i f is equivalent to just f.

That is, "enhancing" f with t i does nothing.

The methods in this class provide us useful ways of navigating a Tensor t with respect to this property.

The Tensor is essentially the HBifunctor equivalent of Inject, with intro1 and intro2 taking the place of inject.

Associated Types

type I t :: Type -> Type Source #

The identity of Tensor t. If you "combine" f with the identity, it leaves f unchanged.

For example, the identity of :*: is Proxy. This is because

(Proxy :*: f) a

is equivalent to just

f a

:*:-ing f with Proxy gives you no additional structure.

Another example:

(V1 :+: f) a

is equivalent to just

f a

because the L1 case is unconstructable.

Methods

intro1 :: f ~> t f (I t) Source #

Because t f (I t) is equivalent to f, we can always "insert" f into t f (I t).

This is analogous to inject from Inject, but for HBifunctors.

intro2 :: g ~> t (I t) g Source #

Because t (I t) g is equivalent to f, we can always "insert" g into t (I t) g.

This is analogous to inject from Inject, but for HBifunctors.

elim1 :: Functor f => t f (I t) ~> f Source #

Witnesses the property that I t is the identity of t: t f (I t) always leaves f unchanged, so we can always just drop the I t.

elim2 :: Functor g => t (I t) g ~> g Source #

Witnesses the property that I t is the identity of t: t (I t) g always leaves g unchanged, so we can always just drop the I t.

Instances
Tensor Day Source # 
Instance details

Defined in Data.HBifunctor.Tensor

Associated Types

type I Day :: Type -> Type Source #

Methods

intro1 :: f ~> Day f (I Day) Source #

intro2 :: g ~> Day (I Day) g Source #

elim1 :: Functor f => Day f (I Day) ~> f Source #

elim2 :: Functor g => Day (I Day) g ~> g Source #

Tensor These1 Source # 
Instance details

Defined in Data.HBifunctor.Tensor

Associated Types

type I These1 :: Type -> Type Source #

Tensor Comp Source # 
Instance details

Defined in Data.HBifunctor.Tensor

Associated Types

type I Comp :: Type -> Type Source #

Methods

intro1 :: f ~> Comp f (I Comp) Source #

intro2 :: g ~> Comp (I Comp) g Source #

elim1 :: Functor f => Comp f (I Comp) ~> f Source #

elim2 :: Functor g => Comp (I Comp) g ~> g Source #

Tensor ((:+:) :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.HBifunctor.Tensor

Associated Types

type I (:+:) :: Type -> Type Source #

Methods

intro1 :: f ~> (f :+: I (:+:)) Source #

intro2 :: g ~> (I (:+:) :+: g) Source #

elim1 :: Functor f => (f :+: I (:+:)) ~> f Source #

elim2 :: Functor g => (I (:+:) :+: g) ~> g Source #

Tensor ((:*:) :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.HBifunctor.Tensor

Associated Types

type I (:*:) :: Type -> Type Source #

Methods

intro1 :: f ~> (f :*: I (:*:)) Source #

intro2 :: g ~> (I (:*:) :*: g) Source #

elim1 :: Functor f => (f :*: I (:*:)) ~> f Source #

elim2 :: Functor g => (I (:*:) :*: g) ~> g Source #

Tensor (Product :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.HBifunctor.Tensor

Associated Types

type I Product :: Type -> Type Source #

Tensor (Sum :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.HBifunctor.Tensor

Associated Types

type I Sum :: Type -> Type Source #

Methods

intro1 :: f ~> Sum f (I Sum) Source #

intro2 :: g ~> Sum (I Sum) g Source #

elim1 :: Functor f => Sum f (I Sum) ~> f Source #

elim2 :: Functor g => Sum (I Sum) g ~> g Source #

rightIdentity :: (Tensor t, Functor f) => f <~> t f (I t) Source #

f is isomorphic to t f (I t): that is, I t is the identity of t, and leaves f unchanged.

leftIdentity :: (Tensor t, Functor g) => g <~> t (I t) g Source #

g is isomorphic to t (I t) g: that is, I t is the identity of t, and leaves g unchanged.

sumLeftIdentity :: f <~> (V1 :+: f) Source #

leftIdentity (intro1 and elim1) for :+: actually does not require Functor. This is the more general version.

sumRightIdentity :: f <~> (f :+: V1) Source #

rightIdentity (intro2 and elim2) for :+: actually does not require Functor. This is the more general version.

prodLeftIdentity :: f <~> (Proxy :*: f) Source #

leftIdentity (intro1 and elim1) for :*: actually does not require Functor. This is the more general version.

prodRightIdentity :: g <~> (g :*: Proxy) Source #

rightIdentity (intro2 and elim2) for :*: actually does not require Functor. This is the more general version.

Monoidal

class (Tensor t, Semigroupoidal t, Interpret (MF t)) => Monoidal t where Source #

A Monoidal t is a Semigroupoidal, in that it provides some type MF t f that is equivalent to one of:

  • I a -- 0 times
  • f a -- 1 time
  • t f f a -- 2 times
  • t f (t f f) a -- 3 times
  • t f (t f (t f f)) a -- 4 times
  • t f (t f (t f (t f f))) a -- 5 times
  • .. etc

The difference is that unlike SF t, MF t has the "zero times" value.

This typeclass lets you use a type like ListF in terms of repeated applications of :*:, or Ap in terms of repeated applications of Day, or Free in terms of repeated applications of Comp, etc.

For example, f :*: f can be interpreted as "a free selection of two fs", allowing you to specify "I have to fs that I can use". If you want to specify "I want 0, 1, or many different fs that I can use", you can use ListF f.

At the high level, the thing that Monoidal adds to Semigroupoidal is inL, inR, and nilMF:

inL    :: f a -> t f g a
inR    :: g a -> t f g a
nilMF  :: I a -> MF t f a

which are like the HBifunctor versions of inject: it lets you inject an f into t f g, so you can start doing useful mixing operations with it. nilMF lets you construct an "empty" MF t.

Also useful is:

toMF :: t f f a -> MF t f a

Which converts a t into its aggregate type MF

Minimal complete definition

appendMF, splitSF, splittingMF, upgradeC

Associated Types

type MF t :: (Type -> Type) -> Type -> Type Source #

The "monoidal functor combinator" induced by t.

A value of type MF t f a is equivalent to one of:

  • I a -- zero fs
  • f a -- one f
  • t f f a -- two fs
  • t f (t f f) a -- three fs
  • t f (t f (t f f)) a
  • t f (t f (t f (t f f))) a
  • .. etc

For example, for :*:, we have ListF. This is because:

Proxy         ~ ListF []         ~ nilMF @(:*:)
x             ~ ListF [x]        ~ inject x
x :*: y       ~ ListF [x,y]      ~ toMF (x :*: y)
x :*: y :*: z ~ ListF [x,y,z]
-- etc.

You can create an "empty" one with nilMF, a "singleton" one with inject, or else one from a single t f f with toMF.

Methods

appendMF :: t (MF t f) (MF t f) ~> MF t f Source #

If a MF t f represents multiple applications of t f to itself, then we can also "append" two MF t fs applied to themselves into one giant MF t f containing all of the t fs.

splitSF :: SF t f ~> t f (MF t f) Source #

Lets you convert an SF t f into a single application of f to MF t f.

Analogous to a function NonEmpty a -> (a, [a])

Note that this is not reversible in general unless we have Matchable t.

splittingMF :: MF t f <~> (I t :+: t f (MF t f)) Source #

An MF t f is either empty, or a single application of t to f and MF t f (the "head" and "tail"). This witnesses that isomorphism.

To use this property, see nilMF, consMF, and unconsMF.

toMF :: t f f ~> MF t f Source #

Embed a direct application of f to itself into a MF t f.

fromSF :: SF t f ~> MF t f Source #

SF t f is "one or more fs", and 'MF t f is "zero or more fs". This function lets us convert from one to the other.

This is analogous to a function NonEmpty a -> [a].

Note that because t is not inferrable from the input or output type, you should call this using -XTypeApplications:

fromSF @(:*:) :: NonEmptyF f a -> ListF f a
fromSF @Comp  :: Free1 f a -> Free f a

pureT :: CM t f => I t ~> f Source #

If we have an I t, we can generate an f based on how it interacts with t.

Specialized (and simplified), this type is:

pureT @Day   :: Applicative f => Identity a -> f a  -- pure
pureT @Comp  :: Monad f => Identity a -> f a        -- return
pureT @(:*:) :: Plus f => Proxy a -> f a            -- zero

Note that because t appears nowhere in the input or output types, you must always use this with explicit type application syntax (like pureT @Day)

upgradeC :: CM t f => proxy f -> (CS t f => r) -> r Source #

If we have a constraint on the Monoidal satisfied, it should also imply the constraint on the Semigroupoidal.

This is basically saying that C (SF t) should be a superclass of C (MF t).

For example, for :*:, this type signature says that Alt is a superclass of Plus, so whenever you have Plus, you should always also have Alt.

For Day, this type signature says that Apply is a superclass of Applicative, so whenever you have Applicative, you should always also have Apply.

This is necessary because in the current class hierarchy, Apply isn't a true superclass of Applicative. upgradeC basically "imbues" f with an Apply instance based on its Applicative instance, so things can be easier to use.

For example, let's say I have a type Parser that is an Applicative instance, but the source library does not define an Apply instance. I cannot use biretract or binterpret with it, even though I should be able to, because they require Apply.

That is:

biretract :: Day Parser Parser a -> Parser a

is a type error, because it requires Apply Parser.

But, if we know that Parser has an Applicative instance, we can use:

upgradeC @Day (Proxy @Parser) biretract
  :: Day Parser Parser a -> a

and this will now typecheck properly.

Ideally, Parser would also have an Apply instance. But we cannot control this if an external library defines Parser.

(Alternatively you can just use biretractT.)

Note that you should only use this if f doesn't already have the SF constraint. If it does, this could lead to conflicting instances. Only use this with specific, concrete fs. Otherwise this is unsafe and can possibly break coherence guarantees.

The proxy argument can be provided using something like Proxy @f, to specify which f you want to upgrade.

Instances
Monoidal Day Source # 
Instance details

Defined in Data.HBifunctor.Tensor

Associated Types

type MF Day :: (Type -> Type) -> Type -> Type Source #

Methods

appendMF :: Day (MF Day f) (MF Day f) ~> MF Day f Source #

splitSF :: SF Day f ~> Day f (MF Day f) Source #

splittingMF :: MF Day f <~> (I Day :+: Day f (MF Day f)) Source #

toMF :: Day f f ~> MF Day f Source #

fromSF :: SF Day f ~> MF Day f Source #

pureT :: CM Day f => I Day ~> f Source #

upgradeC :: CM Day f => proxy f -> (CS Day f -> r) -> r Source #

Monoidal These1 Source # 
Instance details

Defined in Data.HBifunctor.Tensor

Associated Types

type MF These1 :: (Type -> Type) -> Type -> Type Source #

Monoidal Comp Source # 
Instance details

Defined in Data.HBifunctor.Tensor

Associated Types

type MF Comp :: (Type -> Type) -> Type -> Type Source #

Methods

appendMF :: Comp (MF Comp f) (MF Comp f) ~> MF Comp f Source #

splitSF :: SF Comp f ~> Comp f (MF Comp f) Source #

splittingMF :: MF Comp f <~> (I Comp :+: Comp f (MF Comp f)) Source #

toMF :: Comp f f ~> MF Comp f Source #

fromSF :: SF Comp f ~> MF Comp f Source #

pureT :: CM Comp f => I Comp ~> f Source #

upgradeC :: CM Comp f => proxy f -> (CS Comp f -> r) -> r Source #

Monoidal ((:+:) :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.HBifunctor.Tensor

Associated Types

type MF (:+:) :: (Type -> Type) -> Type -> Type Source #

Methods

appendMF :: (MF (:+:) f :+: MF (:+:) f) ~> MF (:+:) f Source #

splitSF :: SF (:+:) f ~> (f :+: MF (:+:) f) Source #

splittingMF :: MF (:+:) f <~> (I (:+:) :+: (f :+: MF (:+:) f)) Source #

toMF :: (f :+: f) ~> MF (:+:) f Source #

fromSF :: SF (:+:) f ~> MF (:+:) f Source #

pureT :: CM (:+:) f => I (:+:) ~> f Source #

upgradeC :: CM (:+:) f => proxy f -> (CS (:+:) f -> r) -> r Source #

Monoidal ((:*:) :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.HBifunctor.Tensor

Associated Types

type MF (:*:) :: (Type -> Type) -> Type -> Type Source #

Methods

appendMF :: (MF (:*:) f :*: MF (:*:) f) ~> MF (:*:) f Source #

splitSF :: SF (:*:) f ~> (f :*: MF (:*:) f) Source #

splittingMF :: MF (:*:) f <~> (I (:*:) :+: (f :*: MF (:*:) f)) Source #

toMF :: (f :*: f) ~> MF (:*:) f Source #

fromSF :: SF (:*:) f ~> MF (:*:) f Source #

pureT :: CM (:*:) f => I (:*:) ~> f Source #

upgradeC :: CM (:*:) f => proxy f -> (CS (:*:) f -> r) -> r Source #

Monoidal (Product :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.HBifunctor.Tensor

Associated Types

type MF Product :: (Type -> Type) -> Type -> Type Source #

Monoidal (Sum :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.HBifunctor.Tensor

Associated Types

type MF Sum :: (Type -> Type) -> Type -> Type Source #

Methods

appendMF :: Sum (MF Sum f) (MF Sum f) ~> MF Sum f Source #

splitSF :: SF Sum f ~> Sum f (MF Sum f) Source #

splittingMF :: MF Sum f <~> (I Sum :+: Sum f (MF Sum f)) Source #

toMF :: Sum f f ~> MF Sum f Source #

fromSF :: SF Sum f ~> MF Sum f Source #

pureT :: CM Sum f => I Sum ~> f Source #

upgradeC :: CM Sum f => proxy f -> (CS Sum f -> r) -> r Source #

type CM t = C (MF t) Source #

Convenient alias for the constraint required for inL, inR, pureT, etc.

It's usually a constraint on the target/result context of interpretation that allows you to "exit" or "run" a Monoidal t.

nilMF :: forall t f. Monoidal t => I t ~> MF t f Source #

Create the "empty MF@.

If MF t f represents multiple applications of t f with itself, then nilMF gives us "zero applications of f".

Note that t cannot be inferred from the input or output type of nilMF, so this function must always be called with -XTypeApplications:

nilMF @Day :: Identity ~> Ap f
nilMF @Comp :: Identity ~> Free f
nilMF @(:*:) :: Proxy ~> ListF f

consMF :: Monoidal t => t f (MF t f) ~> MF t f Source #

Lets us "cons" an application of f to the front of an MF t f.

unconsMF :: Monoidal t => MF t f ~> (I t :+: t f (MF t f)) Source #

"Pattern match" on an MF t

An MF t f is either empty, or a single application of t to f and MF t f (the "head" and "tail")

This is analogous to the function uncons :: [a] -> Maybe (a, [a]).

Utility

inL :: forall t f g. (Monoidal t, CM t g) => f ~> t f g Source #

Convenient wrapper over intro1 that lets us introduce an arbitrary functor g to the right of an f.

You can think of this as an HBifunctor analogue of inject.

inR :: forall t f g. (Monoidal t, CM t f) => g ~> t f g Source #

Convenient wrapper over intro2 that lets us introduce an arbitrary functor f to the right of a g.

You can think of this as an HBifunctor analogue of inject.

outL :: (Tensor t, I t ~ Proxy, Functor f) => t f g ~> f Source #

Convenient wrapper over elim1 that lets us drop one of the arguments of a Tensor for free, without requiring any extra constraints (like for binterpret).

See prodOutL for a version that does not require Functor f, specifically for :*:.

outR :: (Tensor t, I t ~ Proxy, Functor g) => t f g ~> g Source #

Convenient wrapper over elim2 that lets us drop one of the arguments of a Tensor for free, without requiring any constraints (like for binterpret).

See prodOutR for a version that does not require Functor g, specifically for :*:.

biretractT :: forall t f. (Monoidal t, CM t f) => t f f ~> f Source #

This is biretract, but taking a C (MF t) constraint instead of a C (SF t) constraint. For example, for Day, it takes an Applicative constraint instead of an Apply constraint.

In an ideal world, this would be not necessary, and we can use biretract. However, sometimes C (MF t) is not an actual subclass of C (SF t) (like Apply and Applicative), even though it should technically always be so.

Note that you should only use this if f doesn't already have the SF constraint (for example, for Day, if f already has an Apply instance). If it does, this could lead to conflicting instances. If f already has the SF instance, just use biretract directly. Only use this with specific, concrete fs.

binterpretT :: forall t f g h. (Monoidal t, CM t h) => (f ~> h) -> (g ~> h) -> t f g ~> h Source #

This is binterpret, but taking a C (MF t) constraint instead of a C (SF t) constraint. For example, for Day, it takes an Applicative constraint instead of an Apply constraint.

In an ideal world, this would be not necessary, and we can use biretract. However, sometimes C (MF t) is not an actual subclass of C (SF t) (like Apply and Applicative), even though it should technically always be so.

Note that you should only use this if f doesn't already have the SF constraint (for example, for Day, if f already has an Apply instance). If it does, this could lead to conflicting instances. If f already has the SF instance, just use biretract directly. Only use this with specific, concrete fs.

prodOutL :: (f :*: g) ~> f Source #

outL for :*: actually does not require Functor. This is the more general version.

prodOutR :: (f :*: g) ~> g Source #

outR for :*: actually does not require Functor. This is the more general version.

Matchable

class Monoidal t => Matchable t where Source #

For some t, we have the ability to "statically analyze" the MF t and pattern match and manipulate the structure without ever interpreting or retracting. These are Matchable.

Methods

unsplitSF :: t f (MF t f) ~> SF t f Source #

The inverse of splitSF. A consing of f to MF t f is non-empty, so it can be represented as an SF t f.

This is analogous to a function uncurry (:|) :: (a, [a]) -> NonEmpty a.

matchMF :: MF t f ~> (I t :+: SF t f) Source #

"Pattern match" on an MF t f: it is either empty, or it is non-empty (and so can be an SF t f).

This is analgous to a function nonEmpty :: [a] -> Maybe (NonEmpty a).

Note that because t cannot be inferred from the input or output type, you should use this with -XTypeApplications:

matchMF @Day :: Ap f a -> (Identity :+: Ap1 f) a
Instances
Matchable Day Source # 
Instance details

Defined in Data.HBifunctor.Tensor

Methods

unsplitSF :: Day f (MF Day f) ~> SF Day f Source #

matchMF :: MF Day f ~> (I Day :+: SF Day f) Source #

Matchable ((:+:) :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.HBifunctor.Tensor

Matchable ((:*:) :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.HBifunctor.Tensor

Matchable (Product :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.HBifunctor.Tensor

Matchable (Sum :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.HBifunctor.Tensor

Methods

unsplitSF :: Sum f (MF Sum f) ~> SF Sum f Source #

matchMF :: MF Sum f ~> (I Sum :+: SF Sum f) Source #

splittingSF :: Matchable t => SF t f <~> t f (MF t f) Source #

An SF t f is isomorphic to an f consed with an MF t f, like how a NonEmpty a is isomorphic to (a, [a]).

matchingMF :: forall t f. Matchable t => MF t f <~> (I t :+: SF t f) Source #

An MF t f is isomorphic to either the empty case (I t) or the non-empty case (SF t f), like how [a] is isomorphic to Maybe (NonEmpty a).