The Functor Combinatorpedia
by Justin Le ♦
functor-combinators: hackage / github
(Note: This post has been heavily revised to reflect the functor-combinators-0.2 refactoring, as of November 2019. For reference, the original post is available on github.)
(Note 2: The section on contravariant functor combinators was added following the release of functor-combinators-0.3 in August 2020, which added support for contravariant and invariant functor combinators.)
Recently I’ve been very productive what I have been calling the “Functor Combinator” design pattern. It is heavily influenced by ideas like Data types a la Carte and unified free monoidal functors, but the end goal is slightly different in spirit. The goal is to represent schemas, DSL’s, and computations (things like parsers, things to execute, things to consume or produce data) by assembling “self-evident” basic primitives and subjecting them to many different successive transformations and combiners (through combinators, free structures, tensors, and other options). The process of doing so:
- Forces you to make explicit decisions about the structure of your computation type as an ADT.
- Allows you to retain isolation of fundamental parts of your domain as separate types
- Lets you manipulate the structure of your final computation type through normal Haskell techniques like pattern matching. The structure is available throughout the entire process, so you can replace individual components and values within your structure.
- Allows you to fully reflect the structure of your final computation through pattern matching and folds, so you can inspect the structure and produce useful summaries.
Like “data types a la carte” and free monad/applicative/alternative designs, these techniques allow you to separate the assembly and inspection of your programs from the “running” of them.1 However, the main difference is that here we focus not just on products and sums, but many different varied and multi-purpose combinators — a “zoo” of combinators. The fixed point is not the end goal. The actual ADT data types themselves are the goal.
This post is a run-down on the wide variety of such “functor combinators” across the Haskell ecosystem — a functor combinatorpedia. To speak about them all with the same language and vocabulary, this post also serves as an overview of the functor-combinators library, which doesn’t really define these functor combinators, but rather pulls them all together and provides a unified interface for working with them. Most of these types and typeclasses are exported by Data.Functor.Combinator. Of course, the end-goal is to work with these data types themselves directly, so not everything is meant to be doable with these typeclasses; they only serve to unite some common aspects.
Right now I already have some posts about this general design pattern, “Interpreters a la Carte” in Advent of Code 2017 Duet and Applicative Regular Expressions using the Free Alternative, but I do have some posts planned in the future going through projects using this unified interface. In a way, this post also serves as the “introduction to free structures” that I always wanted to write :)
Please refer to the table of contents if you are using this as a reference!
Preface: What is a functor combinator?
A functor combinator takes “functors” (or any other indexed type, k -> Type) and returns a new functor, enhances or mixes them together in some way. That is, they take things of kind k -> Type and themselves return a j -> Type. This lets us build complex functors/indexed types out of simpler “primitive” ones. This includes many some monad transformers, free structures, and tensors.
For example, ReaderT r is a famous one that takes a functor f and enhances it with “access to an r environment” functionality. Another famous one is Free, which takes a functor f and enhances it with “sequential binding” capabilities: it turns f into a Monad.
The main thing that distinguishes these functor combinators from things like monad transformers is that they are “natural on f”: they work on all fs, not just monads, and assume no structure (not even Functor).
Sometimes, we have binary functor combinators, like :+:, which takes two functors f and g and returns a functor that is “either” f or g. Binary functor combinators “mix together” the functionality of different functors in different ways.
Examples
If your final DSL/program/schema is some functor, then functor combinators allow you to construct your final functor by combining simpler “primitive” functors, and take advantage of common functionality.
For example, if you were making a data type/EDSL to describe a command line argument parser, you might have two primitives: data Arg a, for positional arguments parsing a, and data Option a, for --flag non-positional options parsing a. From there, you can choose what structure of command line arguments you want to be able to express.
For instance, a structure that can support multiple arguments and optionally a single Option would be:
type CommandArgs = Ap Arg :*: Lift OptionAnd a structure that supports multiple named commands on top of that would be:
type CommandArgs = MapF String (Ap Arg :*: Lift Option)You can mix or match combinators to decide exactly what sort of structures you allow in your DSL.
Now, instead of writing one “giant” runParser :: MapF String (Ap Arg :*: Lift Option) a -> IO a function, you can instead just write parsers for your simple primitives Arg a -> IO a and Option a -> IO a, and then use functor combinator tools to “promote” them to being runnable on a full MapF String (Ap Arg :*: Lift Option) without any extra work.
Common Functionality
Most of these functor combinators allow us to “swap out” the underlying functor, retaining all of the “enhanced” structure. We abstract over all of these using hmap for single-argument functor combinators (“enhancers”) and hbimap for two-argument functor combinators (“mixers”).
class HFunctor t where -- | Swap out underlying functor for a single-argument functor combinator hmap :: (forall x. f x -> g x) -> t f a -> t g a class HBifunctor t where -- | Swap out underlying functors for a two-argument functor combinator hbimap :: (forall x. f x -> h x) -> (forall x. g x -> j x) -> t f g a -> t h j aHowever, for this post, the concept of a “natural transformation” between f and g — a function of type forall x. f x -> g x, is given a type synonym:
type f ~> g = forall x. f x -> g xThen the type signatures of hmap and hbimap become:
class HFunctor t where hmap :: f ~> g -> t f ~> t g class HBifunctor t where hbimap :: f ~> h -> g ~> j -> t f g ~> t h jWhat does it mean exactly when we say that hmap and hbimap “preserve the enhanced structure”? Well, for example, the type newtype ListF f a = ListF [f a] is essentially a list of f as. hmap will swap out and replace each f a, but it must preserve the relative order between each of the original f as. It must also preserve the length of the list. It’s a complete “in-place swap”. This is formalizing by requiring hmap id == id and hbimap id id == id.
You can also always “lift” a functor value into its transformed type. We abstract over this by using inject (for single-argument functors) and inL and inR (for two-argument functors):
-- single argument functor combinators inject :: f ~> t f -- two-argument functor combinators inL :: MonoidIn t i f => f ~> t f g inR :: MonoidIn t i g => g ~> t f gFinally, in order to use any functor combinators, you have to interpret them into some target context. The choice of combinator imposes some constraints on the target context. We abstract over this using interpret and binterpret:
class Interpret t f where -- | Interpret unary functor combinator interpret :: g ~> f -- ^ interpreting function -> t g ~> f class SemigroupIn t i f where -- | Interpret binary functor combinator binterpret :: g ~> f -- ^ interpreting function on g -> h ~> f -- ^ interpreting function on h -> t g h ~> fHaving the typeclass Interpret (and SemigroupIn) take both t and f means that there are certain limits on what sort of f you can interpret into.
One nice consequence of this approach is that for many such schemas/functors you build, there might be many useful target functors. For example, if you build a command line argument parser schema, you might want to run it in Const String to build up a “help message”, or you might want to run it in Parser to parse the actual arguments or run pure tests, or you might want to run it in IO to do interactive parsing.
For some concrete examples of these functor combinators and their constraints:
instance Monad f => Interpret Free f interpret @Free :: Monad g => (g ~> f) -> Free g a -> f a instance SemigroupIn (:+:) V1 f binterpret @(:+:) :: (g ~> f) -> (h ~> f) -> (g :+: h) a -> f aWe see that interpret lets you “run” a Free in any monad f, and binterpret lets you “run” a function over both branches of an g :+: h to produce an f.
From these, we can also build a lot of useful utility functions (like retract, biretract, getI, biget, etc.) for convenience in actually working on them. These are provided in functor-combinators.
Without further ado, let’s dive into the zoo of functor combinators!
Two-Argument
Binary functor combinators “mix together” two functors/indexed types in different ways.
We can finally interpret (or “run”) these into some target context (like Parser, or IO), provided the target satisfies some constraints.
For the most part, binary functor combinators t are instances of both Associative t and Tensor t i. Every t is associated with i, which is the “identity” functor that leaves f unchanged: t f i is the same as f, and t i f is the same as f as well.
For example, we have Comp, which is functor composition:
newtype Comp f g a = Comp (f (g a))We have an instance Associative Comp and Tensor Comp Identity, because Comp f Identity (composing any functor with Identity, f (Identity a)) is just the same as f a (the original functor); also, Comp Identity f (or Identity (f a)) is the same as f a.
From there, some functors support being “merged” (interpreted, or collapsed) from a binary functor combinator, or being able to be injected “into” a binary functor combinator. Those functors f have instances SemigroupIn t f and MonoidIn t i f. If a functor f is SemigroupIn t f, we can interpret out of it:
binterpret :: SemigroupIn t f => (g ~> f) -> (h ~> f) -> (t g h ~> f) biretract :: SemigroupIn t f => t f f ~> fAnd if a functor f is MonoidIn t i f, we can “inject” into it:
pureT :: MonoidIn t i f => i ~> f inL :: MonoidIn t i g => f ~> t f g inR :: MonoidIn t i f => g ~> t f gA more detailed run-down is available in the docs for Data.Functor.Combinator.
One interesting property of these is that for tensors, if we have a binary functor combinator *, we can represent a type f | f * f | f * f * f | f * f * f * f | ... (“repeatedly apply to something multiple times”), which essentially forms a linked list along that functor combinator. This is like a linked list with t as the “cons” operation, so we call this ListBy t. We can also make a “non-empty variant”, NonEmptyBy t, which contains “at least one f”.
For example, the type that is either a, f a, f (f a), f (f (f a)), etc. is Free f a, so that type ListBy Comp = Free. The type that is either f a, f (f a), f (f (f a)), etc. (at least one layer of f) is Free1 f a, so type NonEmptyBy Comp = Free1.
functor-combinators provides functions like toListBy :: t f f ~> ListBy t f to abstract over “converting” back and forth between t f f a and linked list version ListBy t f a (for example, between Comp f f a and Free f a).
:+: / Sum
Origin: GHC.Generics (for
:+:) / Data.Functor.Sum (forSum)Mixing Strategy: “Either-or”: provide either case, and user has to handle both possibilities. Basically higher-order
Either.data (f :+: g) a = L1 (f a) | R1 (g a) data Sum f g a = InL (f a) | InR (g a)It can be useful for situations where you can validly use one or the other in your schema or functor. For example, if you are describing an HTTP request, we could have
data GET adescribing a GET request anddata POST adescribing a POST request;(GET :+: POST) awould be a functor that describes either a GET or POST request.The person who creates the
f :+: gdecides which one to give, and the person who consumes/interprets/runs thef :+: gmust provide a way of handling bothbinterpret @(:+:) :: (g ~> f) -> (h ~> f) -> (g :+: h) a -> f abinterpretbecomes analogous toeitherfrom Data.EitherIdentity
instance Tensor (:+:) V1 -- | Data type with no inhabitants data V1 af :+: V1is equivalent to justf, because you can never have a value of the right branch.Monoids
instance SemigroupIn (:+:) f instance MonoidIn (:+:) V1 f binterpret @(:+:) :: (g ~> f) -> (h ~> f) -> (g :+: h) a -> f a inL @(:+:) :: f ~> f :+: g inR @(:+:) :: g ~> f :+: g pureT @(:+:) :: V1 ~> hAll haskell functors are monoids in
:+:. You can callbinterpret,inL,inR, etc. with anything.However, note that
pureTis effectively impossible to call, because no values of typeV1 aexist.List type
type NonEmptyBy (:+:) = Step type ListBy (:+:) = StepStepis the result of an infinite application of:+:to the same value:type Step f = f :+: f :+: f :+: f :+: f :+: f :+: ... etc. -- actual implementation data Step f a = Step { stepPos :: Natural , stepVal :: f a }The correspondence is:
L1 x <=> Step 0 x R1 (L1 y) <=> Step 1 y R1 (R1 (L1 z)) <=> Step 2 z -- etc.It’s not a particularly useful type, but it can be useful if you want to provide an
f aalongside “which position” it is on the infinite list.
:*: / Product
Origin: GHC.Generics (for
:*:) / Data.Functor.Product (forProduct)Mixing Strategy: “Both, separately”: provide values from both functors, and the user can choose which one they want to use. Basically a higher-order tuple.
data (f :*: g) a = f a :*: g a data Product f g a = Pair (f a) (g a)It can be useful for situations where your schema/functor must be specified using both functors, but the interpreter can choose to use only one or the other (or both).
prodOutL :: (f :*: g) ~> f prodOutL (x :*: _) = x prodOutR :: (f :*: g) ~> g prodOutR (_ :*: y) = yIdentity
instance Tensor (:*:) Proxy -- | Data type with only a single constructor and no information data Proxy a = Proxyf :*: Proxyis equivalent to justf, because the left hand side doesn’t add anything extra to the pair.Monoids
instance Alt f => SemigroupIn (:*:) f instance Plus f => MonoidIn (:*:) Proxy f binterpret @(:*:) :: Alt f => g ~> f -> h ~> f -> (g :*: h) ~> f inL @(:*:) :: Plus g => f ~> f :*: g inR @(:*:) :: Plus f => g ~> f :*: g pureT @(:*:) :: Plus h => Proxy ~> hAlt, from Data.Functor.Alt in semigroupoids, can be thought of a “higher-kinded semigroup”: it’s likeAlternative, but with noApplicativeconstraint and no identity:class Alt f where (<!>) :: f a -> f a -> f aIt is used to combine the results in both branches of the
:*:.To introduce an “empty” branch, we need
Plus(in Data.Functor.Plus), which is like a higher-kindedMonoid, orAlternativewith noApplicative:class Alt f => Plus f where zero :: f aList type
type NonEmptyBy (:*:) = NonEmptyF type ListBy (:*:) = ListFListF f ais a “list off as”. It represents the possibility of havingProxy(zero items),x :: f a(one item),x :*: y(two items),x :*: y :*: z(three items), etc.It’s basically an ordered collection of
f as:*:d with each other.Proxy <=> ListF [] x <=> ListF [x] x :*: y <=> ListF [x,y] x :*: y :*: z <=> ListF [x,y,z] -- etc.It is useful if you want to define a schema where you can offer multiple options for the
f a, and the interpreter/consumer can freely pick any one that they want to use.NonEmptyFis the version ofListFthat has “at least onef a”.See the information later on
ListFalone (in the single-argument functor combinator section) for more information on usage and utility.
Day
Origin: Data.Functor.Day
Mixing Strategy: “Both, together forever”: provide values from both functors, and the user must also use both.
It can be useful for situations where your schema/functor must be specified using both functors, and the user must also use both.
binterpret @Day :: Apply f -- superclass of Applicative => (g ~> f) -> (h ~> f) -> Day g h ~> fUnlike for
:*:, you always have to interpret both functor values in order to interpret aDay. It’s a “full mixing”.The mechanism for this is interesting in and of itself. Looking at the definition of the data type:
data Day f g a = forall x y. Day (f x) (g y) (x -> y -> a)We see that because
xandyare “hidden” from the external world, we can’t directly use them without applying the “joining” functionx -> y -> a. Due to how existential types work, we can’t get anything out of it that “contains”xory. Because of this, using the joining function requires bothf xandg y. If we only usef x, we can only get, at best,f (y -> a); if we only useg y, we can only get, at best,g (x -> a). In order to fully eliminate both existential variables, we need to get thexandyfrom bothf xandg y, as if the two values held separate halves of the key.Identity
instance Tensor Day IdentityDay f Identityis equivalent to justf, becauseIdentityadds no extra effects or structure.Monoids
instance Apply f => SemigroupIn Day f instance Applicative f => MonoidIn Day Identity f binterpret @Day :: Apply f => (g ~> f) -> (h ~> f) -> Day g h ~> f inL @Day :: Applicative g => f ~> Day f g inR @Day :: Applicative f => g ~> Day f g pureT @Day :: Applicative h => Identity ~> hApply, from Data.Functor.Apply in semigroupoids, is “Applicativewithoutpure”; it only has<*>(called<.>).pureTis essentiallypure :: Applicative h => a -> h a.List type
type NonEmptyBy Day = Ap1 type ListBy Day = ApAp f ais a bunch off xsDayd with each other. It is either:a(zerofs)f a(onef)Day f f a(twofs)Day f (Day f f) a(threefs)- .. etc.
Like
ListFthis is very useful if you want your schema to provide a “bag” off as and your interpreter must use all of them.For example, if we have a schema for a command line argument parser, each
fmay represent a command line option. To interpret it, we must look at all command line options.Ap1is a version with “at least one”f a.See the information later on
Apalone (in the single-argument functor combinator section) for more information on usage and utility.
Comp
Origin: Control.Monad.Freer.Church. Note that an equivalent type is also found in GHC.Generics and Data.Functor.Compose, but they are incompatible with the
HBifunctortypeclass because they require the second input to have aFunctorinstance.Mixing Strategy: “Both, together, sequentially” : provide values from both functors; the user must use both, and in order.
newtype Comp f g a = Comp (f (g a))It can be useful for situations where your schema/functor must be specified using both functors, and the user must use both, but also enforcing that they must use both in the given order: that is, for a
Comp f g, they interpretfbefore they interpretg.binterpret @Comp :: Bind f -- superclass of Monad => (g ~> f) -> (h ~> f) -> Comp g h ~> fUnlike for
:*:, you always have to interpret both functor values. And, unlike forDay, you must interpret both functor values in that order.Identity
instance Tensor Comp IdentityComp f Identityis equivalent to justf, becauseIdentityadds no extra effects or structure.Monoids
instance Bind f => SemigroupIn Comp f instance Monad f => MonoidIn Comp Identity f binterpret @Comp :: Bind f => (g ~> f) -> (h ~> f) -> Comp g h ~> f inL @Comp :: Monad g => f ~> Comp f g inR @Comp :: Monad f => g ~> Comp f g pureT @Comp :: Monad h => Identity ~> hBind, from [Data.Functor.Bind][] in semigroupoids, is “Monadwithoutreturn”; it only has>>=(called>>-).Somewhat serendipitously, the constraint associated with monoids in
Compis none other than the infamousMonad.This might sound familiar to your ears — it’s the realization of the joke that “monads are monoids in the category of (endo)functors”. The idea is that we can make a tensor like
Compover functors, and that “monoids in” that tensor correspond exactly toMonadinstances. A part of the joke that we can now also see is that monads aren’t the only monoids in the category of endofunctors: they’re just the ones that you get when you tensor overComp. But we see now that if you useDayas your tensor, then “monoids in the category of functors overDay” are actuallyApplicativeinstances! And that the monoids over:*:areAltinstances, etc.Theory aside, hopefully this insight also gives you some insight on the nature of
Monadas an abstraction: it’s a way to “interpret” in and out ofComp, which enforces an ordering in interpretation :)List type
type NonEmptyBy Day = Free1 type LIstBy Day = FreeFree f ais a bunch off xs composed with each other. It is either:a(zerofs)f a(onef)f (f a)(twofs)f (f (f a))(threefs)- .. etc.
Freeis very useful because it allows you to specify that your schema can have manyfs, sequenced one after the other, in which the choice of “the nextf” is allowed to depend on the result of “the previousf”.For example, in an interactive “wizard” sort of schema, we can have a functor representing a dialog box with its result type:
data Dialog aWe can then represent our wizard using
Free Dialog a— an ordered sequence of dialog boxes, where the choice of the next box can depend on result of the previous box.Free1is a version with “at least one”f a.See the information later on
Freealone (in the single-argument functor combinator section) for more information on usage and utility.
Aside
Let us pause for a brief aside to compare and contrast the hierarchy of the above functor combinators, as there is an interesting progression we can draw from them.
:+:: Provide either, be ready for both.:*:: Provide both, be ready for either.Day: Provide both, be ready for both.Comp: Provide both, be ready for both (in order).
These1
Origin: Data.Functor.These.
Mixing Strategy: “Either-or, or both”: provide either (or both) cases, and user has to handle both possibilities. An “inclusive either”
data These1 f g a = This1 (f a) | That1 (g a) | These1 (f a) (g a)This can be useful for situations where your schema/functor can be specified using one functor or another, or even both. See description on
:+:for examples.The person who creates the
These1 f gdecides which one to give, and the person who consumes/interprets/runs thef :+: gmust provide a way of handling both situations.binterpret @These :: Alt f => (g ~> f) -> (h ~> f) -> These g h a -> f aYou can also pattern match on the
These1directly to be more explicit with how you handle each of the tree cases.Identity
instance Tensor These V1These1 f V1is equivalent to justf, because it means theThat1andThese1branches will be impossible to construct, and you are left with only theThis1branch.Monoids
instance Alt f => SemigroupIn These1 f instance Alt f => MonoidIn These1 V1 f binterpret @These :: Alt f => (g ~> f) -> (h ~> f) -> These g h ~> f inL @These1 :: Alt g => f ~> Comp f g inR @These1 :: Alt f => g ~> Comp f g pureT @These1 :: Alt h => V1 ~> hYou need at least
Altto be able to interpret out of aThese1, because you need to be able to handle the case where you have bothfandg, and need to combine the result. However, you never need a fullPlusbecause we always have at least one value to use.List type
type ListBy These1 = StepsSteps, the list type, is the result of an infinite application ofThese1to the same value:type Steps f = f `These1` f `These1` f `These1` f `These1` ... etc. -- actual implementation newtype Steps f a = Steps (NEMap Natural (f a)) -- NEMap is a non-empty MapIt essentially represents an infinite sparse array of
f as, where anf amight exist at many different positions, with gaps here and there. There is always at least onef a.Like
Step, it’s not particularly useful, but it can be used in situations where you want a giant infinite sparse array off as, each at a given position, with many gaps between them.I’ve skipped over the the “non-empty” version, which is
ComposeT Flagged Steps; it requires an extra boolean “flag” because of some of the quirks of nonemptiness. I feel it is even less useful thanSteps.
LeftF / RightF
Origin: Data.HBifunctor
Mixing Strategy: “Ignore the left” / “ignore the right”.
data LeftF f g a = LeftF { runLeftF :: f a } data RightF f g a = RightF { runRightF :: g a }You can think of
LeftFas “:+:without the Right case,R1”, orRightFas “:+:without the Left case,L1”.RightFcan be considered a higher-order version of Tagged, which “tags” a value with some type-level information.This can be useful if you want the second (or first) argument to be ignored, and only be used maybe at the type level.
For example,
RightF IgnoreMe MyFunctoris equivalent to justMyFunctor, but you might want to useIgnoreMeas a phantom type to help limit what values can be used for what functions.Identity
Unlike the previous functor combinators, these three are only
Associative, notTensor: this is because there is no functorisuch thatLeftF i gis equal tog, for allg, and no functorisuch thatRightF f iis equal tof, for allf.Constraints
instance SemigroupIn LeftF f instance SemigroupIn RightF fInterpreting out of either of these is unconstrained, and can be done in any context.
List type
type NonEmptyBy LeftF = FlaggedFor
LeftF, the non-empty list type isFlagged, which is thef atupled with aBool. See the information onFlaggedfor more details. This can be useful as a type that marks if anfis made withinject/pureand is “pure” (False), or “tainted” (True). The provider of aFlaggedcan specify “pure or tainted”, and the interpreter can make a decision based on that tag.type NonEmptyBy RightF = StepFor
RightF, the non-empty list type isStep. SeeStepand the information on:+:for more details. This can be useful for having a value off aat “some point”, indexed by aNatural.
Single-Argument
Unary functor combinators usually directly “enhance” a functor with extra capabilities — usually in the form of a typeclass instance, or extra data fields/constructors.
All of these can be “lifted into” with any constraint on f.
class HFunctor t => Inject t where inject :: f ~> t fInject seems very similar to MonadTrans’s lift; the difference is that inject must be natural on f: it can assume nothing about the structure of f, and must work universally the same. MonadTrans, in contrast, requires Monad f.
Each one can also be “interpreted to” certain functors f:
class Inject t => Interpret t f where interpret :: g ~> f -> t g ~> fAn important law is that:
interpret id . inject == idThis means that if we inject and immediately interpret out of, we should never lose any information in f. All of the original structure in f must stay intact: functor combinators only ever add structure.
Coyoneda
Origin: Data.Functor.Coyoneda
Enhancement: The ability to map over the parameter; it’s the free
Functor.Can be useful if
fis created using aGADTthat cannot be given aFunctorinstance.For example, here is an indexed type that represents the type of a “form element”, where the type parameter represents the output result of the form element.
data FormElem :: Type -> Type where FInput :: FormElem String FTextbox :: FormElem Text FCheckbox :: FormElem Bool FNumber :: FormElem IntThen
Coyoneda FormElemhas aFunctorinstance. We can now fmap over the result type of the form element; for example,fmap :: (a -> b) -> Coyoneda FormElem a -> Coyoneda FormElem btakes a form element whose result is anaand returns a form element whose result is ab.Interpret
instance Functor f => Interpret Coyoneda f interpret @Coyoneda :: Functor f => g ~> f -> Coyoneda g ~> fInterpreting out of a
Coyoneda frequires the target context to itself beFunctor. Usually, the context is anApplicativeorMonad, so this is typically always satisfied.For example, if we want to “run” a
Coyoneda FormEleminIO(maybe as an interactive CLI form), this would beinterpret :: (forall x. FormElem x -> IO x) -> Coyoneda FormElem a -> IO a.
ListF / NonEmptyF
Origin: Control.Applicative.ListF
Enhancement: The ability to offer multiple options for the interpreter to pick from;
ListFis the freePlus, andNonEmptyFis the freeAlt.data ListF f a = ListF { runListF :: [f a] } data NonEmptyF f a = NonEmptyF { runNonEmptyF :: NonEmpty (f a) }Can be useful if you want to provide the ability when you define your schema to provide multiple
f as that the interpreter/consumer can freely pick from.For example, for a schema specifying a form, you might have multiple ways to enter a name. If you had a
Nameschemadata Name a, then you can represent “many different potential name inputs” schema asListF Name a.Because this has a
Plusinstance, you can use(<!>) :: ListF f a -> ListF f a -> ListF f ato combine multiple option sets, andzero :: ListF f ato provide the “choice that always fails/is unusuable”.NonEmptyFis a variety ofListFwhere you always have “at least onef a”. Can be useful if you want to ensure, for your interpreter’s sake, that you always have at least onef aoption to pick from. For example,NonEmptyF Name awill always have at least one name schema.This is essentially
f:*:d with itself multiple times;ListFis the linked list list made by:*:, andNonEmptyFis the non-empty linked list made by:*:.x <=> ListF [x] <=> NonEmptyF (x :| []) x :*: y <=> ListF [x,y] <=> NonEmptyF (x :| [y]) x :*: y :*: z <=> ListF [x,y,z] <=> NonEmptyF (x :| [y,z])Interpret
instance Plus f => Interpret ListF f instance Alt f => Interpret NonEmptyF f interpret @ListF :: Plus f => g ~> f -> ListF g ~> f interpret @NonEmptyF :: Alt f => g ~> f -> NonEmptyF g ~> fInterpreting out of a
ListF frequires the target context to bePlus, and interpreting out of aNonEmptyF frequiresAlt(because you will never have the empty case). However, you always have the option to directly pattern match on the list and pick an item you want directly, which requires no constraint.
Ap / Ap1
Enhancement: The ability to provide multiple
fs that the interpreter must consume all of;Apis the freeApplicative, andAp1is the freeApply.While
ListFmay be considered “multiple options offered”,Apcan be considered “multiple actions all required”. The interpreter must consume/interpret all of the multiplefs in order to interpret anAp.For example, for a form schema, you might want to have multiple form elements. If a single form element is
data FormElem a, then you can make a multi-form schema withAp FormElem a. The consumer of the form schema must handle everyFormElemprovided.Note that ordering is not enforced: while the consumer must handle each
feventually, they are free to handle it in whatever order they desire. In fact, they could even all be handled in parallel. SeeFreefor a version where ordering is enforced.Because this has an
Applicativeinstance, you can use(<*>) :: Ap f (a -> b) -> Ap f a -> Ap f bto sequence multipleAp fs together, andpure :: a -> Ap f ato produce a “no-op”Apwithout anyfs.Aphas some utility overFreein that you can pattern match on the constructors directly and look at each individual sequencedf a, for static analysis, before anything is ever run or interpreted.Structurally,
Apis built like a linked list off xs, which each link being existentially bound together:data Ap :: (Type -> Type) -> Type -> Type where Pure :: a -> Ap f a Ap :: f a -> Ap f (a -> b) -> Ap f bPureis like “nil”, andApis like “cons”:data List :: Type -> Type where Nil :: List a Cons :: a -> List a -> List aThe existential type in the
Apbranch plays the same role that it does in the definition ofDay(see the description ofDayfor more information).Ap1is a variety ofApwhere you always have to have “at least onef”. Can be useful if you want to ensure, for example, that your form has at least one element.Note that this is essentially
fDayd with itself multiple times;Apis the linked list made byDayandAp1is the non-empty linked list made byDay.Interpret
instance Applicative f => Interpret Ap f instance Apply f => Interpret Ap1 f interpret @Ap :: Applicative f => g ~> f -> Ap g ~> f interpret @Ap1 :: Apply f => g ~> f -> Ap1 g ~> fInterpreting out of an
Ap frequires the target context to beApplicative, and interpreting out of aAp1 frequiresApply(because you will never need the pure case).
Alt
Origin: Control.Alternative.Free
Enhancement: A combination of both
ListFandAp: provide a choice (ListF-style) of sequences (Ap-style) of choices of sequences of choices ….; it’s the freeAlternative.Alt f ~ ListF (Ap (ListF (Ap (ListF (Ap (...)))) ~ ListF (Ap (Alt f))This type imbues
fwith both sequential “must use both” operations (via<*>) and choice-like “can use either” operations (via<|>).It can be useful for implementing parser schemas, which often involve both sequential and choice-like combinations. If
fis a primitive parsing unit, thenAlt frepresents a non-deterministic parser of a bunch offs one after the other, with multiple possible results. I wrote an entire article on the usage of this combinator alone to implement a version of regular expressions.Interpret
instance Alternative f => Interpret Alt f interpret @Alt :: Alternative f => g ~> f -> Alt g ~> fInterpreting out of an
Alt frequires the target context to beAlternative— it uses<*>for sequencing, and<|>for choice.
Free / Free1
Origin: Control.Monad.Freer.Church, which is a variant of Control.Monad.Free that is compatible with
HFunctor.Enhancement: The ability to provide multiple
fs that the interpreter must consume in order, sequentially — the freeMonad.Contrast with
Ap, which also sequences multiplefs together, but without any enforced order. It does this by hiding the “nextf a” until the previousf ahas already been interpreted.Perhaps more importantly, you can sequence
fs in a way where the choice of the nextfis allowed to depend on the result of the previousf.For example, in an interactive “wizard” sort of schema, we can create a functor to represent a dialog box with its result type:
data Dialog aWe can then construct a type for a wizard:
type Wizard = Free DialogWizardis now an ordered sequence of dialog boxes, where the choice of the next box can depend on result of the previous box. Contrast toAp Dialog, where the choice of all dialog boxes must be made in advanced, up-front, before reading any input from the user.In having this, however, we loose the ability to be able to inspect each
f abefore interpreting anything.Because this has a
Monadinstance, you can use(<*>) :: Free f (a -> b) -> Free f a -> Free f band(>>=) :: Free f a -> (a -> Free f b) -> Free f b)to sequence multipleFree fs together, andpure :: a -> Free f ato produce a “no-op”Freewithout anyfs.Free1is a variety ofFree1where you always have to have “at least onef”. Can be useful if you want to ensure, for example, that your wizard has at least one dialog box.type NonEmptyWizard = Free1 DialogNote that this is essentially
fCompd with itself multiple times;Freeis the linked list made byCompandFree1is the non-empty linked list made byComp.Interpret
instance Monad f => Interpret Free f instance Bind f => Interpret Free1 f interpret @Free :: Monad f => g ~> f -> Free g ~> f interpret @Free1 :: Bind f => g ~> f -> Free1 g ~> fInterpreting out of a
Free frequires the target context to beMonad, and interpreting out of aFree1 frequiresBind(because you will never need the pure case).
Lift / MaybeApply
Origin: Control.Applicative.Lift / Data.Functor.Apply (the same type)
Enhancement: Make
f“optional” in the schema in a way that the interpreter can still work with as if thefwas still there; it’s the freePointed.data Lift f a = Pure a | Other (f a) newtype MaybeApply f a = MaybeApply { runMaybeApply :: Either a (f a) } -- ^ same type, from semigroupoidsCan be useful so that an
f ais optional for the schema definition, but in a way where the consumer can still continue from it as if they had thef.It can be used, for example, to turn an required parameter
Param ainto an optional parameterLift Param a.Contrast this to
MaybeF: this allows the interpreter to still “continue on” as normal even if thefis not there. However,MaybeFforces the interpreter to abort if thefis not there.This can be thought of as
Identity :+: f.Interpret
instance Pointed f => Interpret Lift f interpret @Lift :: Pointed f => g ~> f -> Lift g ~> fInterpreting out of a
Lift frequires the target context to bePointed, from Data.Pointed — it usespoint :: Pointed f => a -> f ato handle the case where thefis not there.
MaybeF
Origin: Control.Applicative.ListF
Enhancement: Make
f“optional” in the schema in a way that the interpreter must fail if thefis not present.newtype MaybeF f a = MaybeF { runMaybeF :: Maybe (f a) }Can be useful so that an
f ais optional for the schema definition; if thefis not present, the consumer must abort the current branch, or find some other external way to continue onwards.Contrast this to
Lift, which is an “optional”fthat the consumer may continue on from.Interpret
instance Plus f => Interpret MaybeF f interpret @MaybeF :: Plus f => g ~> f -> MaybeF g ~> fInterpreting out of a
Lift frequires the target context to bePlus— it useszero :: f ato handle the case where thefis not there. Note that this is actually “over-constrained”: we really only needzero, and not all ofPlus(which includes<!>). However, there is no common typeclass in Haskell that provides this, so this is the most pragmatic choice.
EnvT
Origin: Control.Comonad.Trans.Env
Enhancement: Provide extra (monoidal) data alongside
f athat the interpreter can access. Basically tuples extraealongside thef a.newtype EnvT e f a = EnvT e (f a)You can use this to basically tuple some extra data alongside an
f a. It can be useful if you want to provide extra information that isn’t inside theffor the interpreter use for interpretation.When using
inject :: Monoid e => f a -> EnvT e f a, it usesmemptyas the initialevalue.One of my personal favorite uses of
EnvTis the flare purescript library, which uses theeas the observed HTML of a form, and thef aas an active way to get information from a form interactively.injectis used to insert an active form element without caring about its HTML representation, andinterpretwould “run” the active elements to get the results.This type exists specialized a few times here, as well:
StepisEnvT (Sum Natural)FlaggedisEnvT Any
Interpret
instance Interpret (EnvT e) f interpret @(EnvT e) :: g ~> f -> EnvT e g ~> fInterpreting out of
EnvT erequires no constraints.
MapF / NEMapF
Origin: Control.Applicative.ListF
Enhancement: Contain multiple
f as, each indexed at a specific key.newtype MapF k f a = MapF { runMapF :: Map k (f a) } newtype NEMapF k f a = NEMapF { runMapF :: NEMap k (f a) }This is very similar in functionality to
ListFandNonEmptyF, except instead of “positional” location, eachf aexists at a given index.NEMapF kis the “non-empty” variant. You can think of this as aListFplusEnvT: it’s a “container” of multiplef as, but each one exists with a given “tag” indexk.In usage, like for
ListF, the definer provides multiple “labeled”f as, and the interpreter can choose to interpret some or all of them, with access to each labeled.injectcreates a singletonMapat keymempty.This is very useful in schemas that have sub-schemas indexed at specific keys. For example, in a command line argument parser, if we have a functor that represents a single command:
data Command aWe can immediately promote it to be a functor representing multiple possible named commands, each at a given string:
type Commands = MapF String CommandSo we can implement “git push” and “git pull” using:
push :: Command Action pull :: Command Action gitCommands :: Commands Action gitCOmmands = MapF . M.fromList $ [ ("push", push) , ("pull", pull) ]This is also useful for specifying things like routes in a server.
This type exists specialized as
Steps, which isNEMapF (Sum Natural).Interpret
instance Plus f => Interpret (MapF k) f instance Alt f => Interpret (NEMap k) f interpret @(MapF k) :: Plus f => g ~> f -> MapF g ~> f interpret @(NEMapF k) :: Alt f => g ~> f -> NEMapF g ~> fInterpreting out of a
MapF k frequires the target context to bePlus, and interpreting out of aNEMapF k frequiresAlt(because you will never have the empty case). However, you can directly look up into theMapand pick an item you want directly, which requires no constraint.
ReaderT
Origin: Control.Monad.Trans.Reader
Enhancement: Provide each
f awith access to some “environment”r.newtype ReaderT r f a = ReaderT { runReaderT :: r -> f a }ReaderT ris often used to model some form of dependency injection: it allows you to work “assuming” you had anr; later, when you run it, you provide ther. It delays the evaluation of your final result until you provide the missingr.Another way of looking at it is that it makes your entire functor have values that are parameterized with an
r.For example, if you have a form data type:
data FormElem ayou can now make a form data type that is parameterized by the current server hostname:
type FormElemWithHost = ReaderT HostName FormElemThe actual structure of your
FormElemis deferred until you provide theHostName.Note that, unlike
ReaderT, most monad transformers from transformers are actually not valid functor combinators under our perspective here, because most of them are not natural onf: they requireFunctor f, at least, to implementinjectorhmap.Interpret
instance MonadReader r f => Interpret (ReaderT r) f interpret @(ReaderT r) :: MonadReader r f => g ~> f -> ReaderT r g ~> fInterpreting out of a
ReaderT rrequires requires the target context to beMonadReader r, which means it must have access toask :: MonadReader r f => f r.In a way,
ReaderT ris the “free” instance ofMonadReader r.
Step
Origin: Control.Applicative.Step
Enhancement: Tuples the
f awith an extra natural number index.data Step f a = Step { stepPos :: Natural, stepVal :: f a }This is essentially a specialized
EnvT: it’sEnvT (Sum Natural).This is a useful type because it can be seen as equivalent to
f :+: f :+: f :+: f :+: f ...forever: it’s anf, but at some index. In Control.Applicative.Step, we have specialized functionsstepUpandstepDown, which allows you to “match” on the “first”fin that infinite chain; it will increment and decrement the index relatively to make this work properly.Interpret
instance Interpret Step f interpret @Step :: g ~> f -> Step g ~> fInterpreting out of
Steprequires no constraints; we just drop theNaturaldata.
Steps
Origin: Control.Applicative.Step
Enhancement: The ability to offer multiple indexed options for the interpreter to pick from. Like
NonEmptyF, except with eachf aexisting at an indexed position that the consumer/interpreter can look up or access.newtype Steps f a = Steps { getSteps :: NEMap Natural (f a) }This is like a mix between
NonEmptyFandStep: multiplef aoptions (at least one) for the consumer/interpreter to pick from. UnlikeNonEmptyF, eachf aexists at an “index” — there might be one at 0, one at 5, one at 100, etc.Another way of looking at this is like an infinite sparse array of
f as: it’s an inifinitely large collection where each spot may potentially have anf a.Useful for “provide options that the consumer can pick from, index, or access”, like
ListF/NonEmptyF.This type can be seen as an infinite
f `These1` f `These1` f `These1` f ..., and along these lines,stepsDownandstepsUpexist inside Control.Applicative.Step analogous tostepUpandstepDownto treat aStepsin this manner.Interpret
instance Alt f => Interpret Steps f interpret @Steps :: Alt f => g ~> f -> Steps g ~> fInterpreting out of
Stepsrequires anAltto combine different possibilities. It does not require a fullPlusconstraint because we never needzero: aSteps f aalways has at least onef a.
Flagged
Origin: Control.Applicative.Step
Enhancement: The ability to “tag” a functor value with a
True/Falseboolean value.data Flagged f a = Flagged { flaggedFlag :: Bool, flaggedVal :: f a }This is essentially a specialized
EnvT: it’sEnvT Any.If created with
injectorpure, it adds the flagFalse. This is helpful for helping indicate if the value was created using a “pure” method likeinjectorpure, or an “impure” method (any other method, including direct construction).Interpret
instance Interpret Flagged f interpret @Flagged :: g ~> f -> Flagged g ~> fInterpreting out of
Flaggedrequires no constraints; we just drop the boolean flag.
Final
Origin: Data.HFunctor.Final
Enhancement:
Final cwill liftfinto a free structure of any typeclassc; it will give it all of the actions/API of a typeclass for “free”.Final c fis the “freec” overf.data Final c f aIn a way, this is the “ultimate free structure”: it can fully replace all other free structures of typeclasses of kind
Type -> Type. For example:Coyoneda ~ Final Functor ListF ~ Final Plus NonEmptyF ~ Final Alt Ap ~ Final Applicative Ap1 ~ Final Apply Free ~ Final Monad Free1 ~ Final Bind Lift ~ Final Pointed IdentityT ~ Final UnconstrainedAll of these are connections are witnessed by instances of the typeclass
FreeOfin Data.HFunctor.Final.In fact,
Final cis often more performant for many operations than the actual concrete free structures.The main downside is that you cannot directly pattern match on the structure of a
Final cthe same way you can pattern match on, say,AporListF. However, you can get often around this by usingFinal Plusfor most of your operations, and theninterpret inject-ing it intoListFwhen you want to actually pattern match.You can also think of this as the “ultimate
Interpret”, because withinjectyou can pushfintoFinal c f, and withinterpretyou only ever need thecconstraint to “run”/interpret this.So, next time you want to give an
fthe ability to<*>andpure, you can throw it intoFinal Applicative:fnow gets “sequencing” abilities, and is equivalent toAp f.If you want the API of a given typeclass
c, you can injectfintoFinal c, and you get the API of that typeclass for free onf.Constraint
instance c f => Interpret (Final c) f interpret @(Final c) :: c f => g ~> f -> Final c g ~> fInterpreting out of a
Final crequiresc, since that is the extra context thatfis lifted into.
Chain / Chain1
Origin: Data.HFunctor.Chain
Enhancement:
Chain twill liftfinto a linked list offs chained byt.-- i is intended to be the identity of t data Chain t i f a = Done (i a) | More (t f (Chain t i f a))For example, for
:*:,Chain (:*:) Proxy fis equivalent to one of:Proxy <=> Done Proxy <=> ListF [] x <=> More (x :*: Done Proxy) <=> ListF [x] x :*: y <=> More (x :*: More (y :*: Done Proxy)) <=> ListF [x,y] -- etc.For
:+:,Chain (:+:) V1 fis equivalent to one of:L1 x <=> More (L1 x) <=> Step 0 x R1 (L1 y) <=> More (R1 (More (L1 y))) <=> Step 1 y R1 (R1 (L1 z)) <=> More (R1 (More (R1 (More (L1 z))))) <=> Step 2 z -- etc.This is useful because it provides a nice uniform way to work with all “linked list over tensors”. That’s because the following types are all isomorphic:
ListF ~ Chain (:*:) Proxy Ap ~ Chain Day Identity Free ~ Chain Comp Identity Step ~ Chain (:+:) Void Steps ~ Chain These1 VoidThis isomorphism is witnessed by
unroll(turn into theChain) andreroll(convert back from theChain) in Data.HFunctor.Chain.We can “fold down” a
Chain t (I t) f ainto anf a, iftisMonoidal, usinginterpret id. In fact, this ability could be used as a fundamental property of monoidal nature.We also have a “non-empty” version,
Chain1, for non-empty linked lists over tensors:data Chain1 t f a = Done1 (f a) | More1 (t f (Chain1 t f a))NonEmptyF ~ Chain1 (:*:) Ap1 ~ Chain1 Day Free1 ~ Chain1 Comp Step ~ Chain1 (:+:) Steps ~ Chain1 These1 EnvT Any ~ Chain1 LeftF Step ~ Chain1 RightFWe can “fold down” a
Chain1 t f ainto anf a, iftisSemigroupoidal, usinginterpret id. In fact, this ability could be used as a fundamental property of semigroupoidal nature.Using
ListF,Ap,Free,Step,Steps, etc. can sometimes feel very different, but withChainyou get a uniform interface to pattern match on (and construct) all of them in the same way.Using
NonEmptyF,Ap1,Free1,Step,Flagged, etc. can sometimes feel very different, but withChain1you get a uniform interface to pattern match on (and construct) all of them in the same way.Universally, we can concatenate linked chains, with:
appendChain :: Tensor t i => t (Chain t i f) (Chain t i f) ~> Chain t i f appendChain1 :: Associative t => t (Chain1 t f) (Chain1 t f) ~> Chain1 t fThese operations are associative, and this property is gained from the tensor nature of
t.The construction of
Chainis inspired by Oleg Grenrus’s blog post, and the construction ofChain1is inspired by implementations of finite automata and iteratees.Interpret
instance MonoidIn t i f => Interpret (Chain t i) f instance SemigroupIn t f => Interpret (Chain1 t ) f interpret @(Chain t i) :: MonoidIn t i f => g ~> f -> Chain t i g ~> f interpret @(Chain1 t) :: SemigroupIn t f => g ~> f -> Chain1 t g ~> fInterpreting out of a
Chainrequires only thatfis a monoid int. Interpreting out of aChain1requires only thatfis a semigroup int.For example, we have:
instance Plus f => Interpret (Chain (:*:) Proxy) f instance Alt f => Interpret (Chain1 (:*:) ) f interpret @(Chain (:*:) Proxy) :: Plus f => g ~> f -> Chain (:*:) Proxy g ~> f interpret @(Chain1 (:*:)) :: Alt f => g ~> f -> Chain1 (:*:) f ~> f instance Applicative f => Interpret (Chain Day Identity) f instance Apply f => Interpret (Chain1 Day ) f instance Monad f => Interpret (Chain Comp Identity) f instance Bind f => Interpret (Chain1 Comp ) f
IdentityT
Origin: Data.Functor.Identity
Enhancement: None whatsoever; it adds no extra structure to
f, andIdentityT fis the same asf; it’s the “freeUnconstrained”data IdentityT f a = IdentityT { runIdentityT :: f a }This isn’t too useful on its own, but it can be useful to give to the functor combinator combinators as a no-op functor combinator. It can also be used to signify “no structure”, or as a placeholder until you figure out what sort of structure you want to have.
In that sense, it can be thought of as a “
ListFwith always one item”, a “MaybeFthat’s alwaysJust”’, an “Apwith always one sequenced item”, a “Freewith always exactly one layer of effects”, etc.Constraint
instance Interpret IdentityT f interpret @IdentityT :: g ~> f -> IdentityT g ~> fInterpreting out of
IdentityTrequires no constraints — it basically does nothing.
ProxyF / ConstF
Origin: Data.HFunctor
Enhancement: “Black holes” — they completely forget all the structure of
f, and are impossible tointerpretout of.Impossible“.data ProxyF f a = ProxyF data ConstF e f a = ConstF eProxyFis essentiallyConstF ().These are both valid functor combinators in that you can inject into them, and
interpret id . inject == idis technically true (the best kind of true).You can use them if you want your schema to be impossible to interpret, as a placeholder or to signify that one branch is uninterpretable. In this sense, this is like a “
ListFthat is always empty” or a “MaybeFthat is alwaysNothing”.Because of this, they aren’t too useful on their own — they’re more useful in the context of swapping out and combining or manipulating with other functor combinators or using with functor combinator combinators.
Interpret
You’re not going to have any luck here — you cannot interpret out of these, unfortunately!
Contravariant Functor Combinators
Addendum: Post functor-combinators-0.3.0.0
Most of the above functor combinators have been “covariant” ones: an t f a represents some “producer” or “generator” of as. Many of them require a Functor constraint on f interpret out of. However, there exist many useful contravariant ones too, where t f a represents a “consumer” of as; many of these require a Contravariant constraint on f to interpret out of. These can be useful as the building blocks of consumers like serializers.
I’ve included them all in a separate section because you to either be looking for one or the other, and also because there are much less contravariant combinators than covariant ones in the Haskell ecosystem.
Also note that many of the functor combinators in the previous sections are compatible with both covariant and contravariant functors, like:
:+:/SumLeftF/RightFEnvTStepFlaggedFinalChainIdentityT
The following functor combinators in the previous section are also compatible with both, but their instances in functor-combinator are designed around covariant usage. However, some of them have contravariant twins that are otherwise identical except for the fact that their instances are instead designed around contravariant usage.
:*:/Product(contravariant version: the contravariantDay)These1ListF/NonEmptyF(contravariant versions:DivandDiv1)MaybeF
This section was added following the release of functor-combinators-0.3.0.0, which added in support for contravariant and invariant functor combinators.
Contravariant Day
Origin: Data.Functor.Contravariant.Day
Mixing Strategy: “Both, together”: provide two consumers that are each meant to consume one part of the input.
data Day f g a = forall x y. Day (f x) (g y) (a -> (x, y))This type is essentially equivalent to
:*:/ProductiffisContravariant, so it is useful in every situation where:*:would be useful. It can be thought of as simply a version of:*:that signals to the reader that it is meant to be used contravariantly (as a consumer) and not covariantly (as a producer).Like for
:*:, it has the distinguishing property (iffisContravariant) of allowing you to use either thefor theg, as you please.dayOutL :: Contravariant f => Day f g ~> f dayOutL (Day x _ f) = contramap (fst . f) x dayOutR :: Contravariant g => Day f g ~> g dayOutR (Day _ y f) = contramap (snd . f) yIn practice, however, I like to think of it as storing an
fand agthat can each handle a separate “part” of ana. For example, the illustrative helper functionday :: f a -> g b -> Day f g (a, b) day x y = Day x y idallows you to couple an
f aconsumer ofawith ag bconsumer ofbto produce a consumer of(a, b)that does its job by handing theatox, and thebtoy.Identity
instance Tensor Day ProxySince this type is essentially
(:*:), it has the same identity.day Proxy :: g b -> Day Proxy g (a, b)is the
Daythat would “ignore” theapart and simply pass thebtog.Monoids
instance Divise f => SemigroupIn Day f instance Divisible f => MonoidIn Day Proxy f binterpret @Day :: Divise f => g ~> f -> h ~> f -> Day g h ~> f inL @(:*:) :: Divisible g => f ~> Day f g inR @(:*:) :: Divisible f => g ~> Day f g pureT @(:*:) :: Divisible h => Proxy ~> hDivisefrom Data.Functor.Contravariant.Divise can be thought of some version the “contravariantAlt”: it gives you a way to merge twof as into a single one in a way that represents having both the items consume the input as they choose. The usual way of doing this is by providing a splitting function to choose to give some part of the input to one argument, and some part to another:class Contravariant f => Divise f where divise :: (a -> (b, c)) -> f b -> f c -> f a -- ^ what to give to the 'f b' -- ^ what to give to the 'f c'Divisiblefrom Data.Functor.Contravariant.Divisible, adds an identity that will ignore anything it is given:conquer.class Divise f => Divisible f where conquer :: f a(note: like with
ApplicativeandApply, the actual version requires onlyContravariant f;Diviseisn’t an actual superclass, even though it should be.)List type
Basically,
type NonEmptyBy Day = NonEmptyF type ListBy Day = ListFBecause the contravariant
Dayis equivalent to:*:for contravariant inputs, they have the exact same “list type”. However, in the functor-combinators library, each list type can only have a singleInterpretinstance, so instead the list types are defined to be a separate (identical) type with a different name:type NonEmptyBy Day = Div1 type ListBy Day = DivLike for
Day, it’s something that can be used instead of:*:to mentally signify how the type is meant to be used. You can think ofDiv f aas a chain offs, where theais distributed over eachf, but the intent of its usage is that eachfis meant to consume a different part of thata.See the information later on
Divalone for more information on usage and utility.Divis the possibly-empty version, andDiv1is the nonempty version.
Night
Origin: Data.Functor.Contravariant.Night
Mixing Strategy: “One or the other, but chosen at consumption-time”: provide two consumers to handle input, but the choice of which consumer to use is made at consumption time.
data Night f g a = forall x y. Night (f x) (g y) (a -> Either x y)This one represents delegation:
Night f g acontainsfandgthat could process some form of thea, but which of the two is chosen to depends on the value ofaitself.This can be thought of as representing sharding between
fandg. Some discriminator determins which offorgis better suited to consume the input, and picks which single one to use based on that.The illustrative helper function can make this clear:
night :: f a -> g b -> Night f g (Either a b) night x y = Night x y idallows you to couple an
f aconsumer ofawith ag bconsumer ofbto produce a consumer ofEither a bthat does its job by using thefif given aLeftinput, and using thegif given abinput.This is technically still a day convolution (mathematically), but it uses
Eitherinstead of the typical(,)we use in Haskell. So it’s like the opposite of a usual HaskellDay— it’sNight:)Identity
instance Tensor Night Not -- | Data type that proves @a@ cannot exist newtype Not a = Not { refute :: a -> Void }If
Night f gassigns input to eitherforg, then a functor that “cannot be chosen”/“cannot be used” would force the choice to the other side.That is,
Night f Notmust necessarily pass its input tof, as you cannot pass anything to aNot, since it only accepts passing in uninhabited types.Monoids
instance Decide f => SemigroupIn Night f instance Conclude f => MonoidIn Night Not f binterpret @Night :: Decide f => g ~> f -> h ~> f -> Night g h ~> f inL @Night :: Conclude g => f ~> Night f g inR @Night :: Conclude f => g ~> Night f g pureT @Night :: Conclude h => Not ~> hDecidefrom Data.Functor.Contravariant.Decide can be thought of as a deterministic sharding typeclass: You can combine two consumers along with a decision function on which consumer to use.class Contravariant f => Decide f where decide :: (a -> Either b c) -> f b -> f c -> f a -- ^ use the f b -- ^ use the f cConcludefrom Data.Functor.Contravariant.Conclude, adds support for specifying anfthat cannot be chosen by the decision function when used withdecide.class Decide f => Conclude f where conclude :: (a -> Void) -> f aList type
type NonEmptyBy Night = Dec1 type ListBy Night = DecDec fandDec1 frepresent a bunch offsNight’d with each other — you can think ofDec fwas the sharding over many differentfs (or even none), andDec1 fas the sharding over at least onef.See the later section on
Decfor more information.
Contravariant Coyoneda
Enhancement: The ability to contravariantly map over the parameter; it’s the free
Contravariant.Can be useful if
fis created using aGADTthat cannot be given aContravariantinstance.For example, here is an indexed type that represents the type of a “prettyprinter”, where the type parameter represents the type that is being pretty-printed output result of the form element.
data PrettyPrim :: Type -> Type where PPString :: PrettyPrim String PPInt :: PrettyPrim Int PPBool :: PrettyPrim BoolThen
Coyoneda PrettyPrimhas aContravariantinstance. We can now contramap over the input type of the pretty-printer; for example,contramap :: (a -> b) -> Coyoneda PrettyPrim b -> Coyoneda PrettyPrim atakes a prettyprinter ofbs and turns it into a prettyprinter ofas.Interpret
instance Contravariant f => Interpret Coyoneda f interpret @Coyoneda :: Contravariant f => g ~> f -> Coyoneda g ~> fInterpreting out of a
Coyoneda frequires the target context to itself beContravariant. For example, if we want to “run” aCoyoneda PrettyPriminOp String(Op String ais a function fromatoString), this would beinterpret :: (forall x. PrettyPrim x -> Op String x) -> Coyoneda PrettyPrim a -> Op String a.
Div / Div1
Enhancement: The ability to provide multiple
fs to each consume a part of the overall input.If
f xis a consumer ofxs, thenDiv f ais a consumer ofas that does its job by splittingaacross /all/fs, forking them out in parallel. Often times, in practice, this will utilized by giving eachfa separate part of theato consume.For example, let’s say you had a type
Socket awhich represents some IO channel or socket that is expecting to receiveas. ADiv Socket bwould be a collection of sockets that expects a singleboverall, but each individualSocketinside thatDivis given some part of the overallb.Another common usage is to combine serializers by assigning each serializer
fto one part of an overall input.Structurally,
DivandDiv1are basically lists of contravariant coyonedas:newtype Div f a = Div { unDiv :: [Coyoneda f a] } newtype Div1 f a = Div1 { unDiv1 :: NonEmpty (Coyoneda f a) }This could be implemented as simply a normal
[f a]andNonEmpty (f a)(and so making them identical toListF). For the most part, you could use the two interchangely, except in the case where you need toInterpretout of them:ListFrequires aPlusconstraint, andDivrequires aDivisibleconstraint. TheCoyonedais also necessary for compatibility with the version of the contravariantDayconvolution provided by kan-extensions.Div1is a variety ofDivwhere you always have to have “at least onef”. Can be useful if you want to ensure, for example, that at least one socket will be handling the input (and it won’t be lost into the air).Interpret
instance Divisible f => Interpret Div f instance Divise f => Interpret Div1 f interpret @Div :: Divisible f => g ~> f -> Div g ~> f interpret @Div1 :: Divise f => g ~> f -> Div1 g ~> fInterpreting out of an
Div frequires the target context to beDivisible, and interpreting out of aDiv1 frequiresDivise(because you will never need the empty case).
Dec / Dec1
Enhancement: The ability to provide multiple
fs, one of which will be chosen to consume the overall input.If
f xis a consumer ofxs, thenDec f ais a consumer ofas that does its job by choosing a single one of thosefs to handle that consumption, based on whatais received.Contrast this with
Div, where the multiplefactions are all used to consume the input.Deconly uses one singlefaction to consume the input, chosen at consumption time.For example, let’s say you had a type
Socket awhich represents some IO channel or socket that is expecting to receiveas. ADec Socket bwould be a collection of sockets that expects a singleboverall, and will pick exactly one of thoseSockets to handle thatb.In this sense, you can sort of think of
Decas a “sharding” offs: eachfhandles a different possible categorization of the input.Another common usage is to combine serializers by assigning each serializer
fto one possible form of possible input.Structurally,
Decis built like a linked list off xs, which each link being existentially bound together:data Dec :: (Type -> Type) -> Type -> Type where Lose :: (a -> Void) -> Dec f a Choose :: f x -> Dec f y -> (a -> Either x y) -> Dec f aThis is more or less the same construction as for
Ap: see information onApfor a deeper explanation on how or why this works.Dec1is a variety ofDecwhere you always have to have “at least onef”. Can be useful if you want to ensure, for example, that there always exists at least onefthat can handle the job.Interpret
instance Conclude f => Interpret Dec f instance Decide f => Interpret Dec1 f interpret @Dec :: Conclude f => g ~> f -> Dec g ~> f interpret @Dec1 :: Decide f => g ~> f -> Dec1 g ~> fInterpreting out of an
Dec frequires the target context to beConclude, and interpreting out of aDec1 frequiresDecide(because you will never need the rejecting case).
Combinator Combinators
There exist higher-order functor combinator combinators that take functor combinators and return new ones, too. We can talk about a uniform interface for them, but they aren’t very common, so it is probably not worth the extra abstraction.
ComposeT
Origin: Control.Monad.Trans.Compose
Enhancement: Compose enhancements from two different functor combinators
newtype ComposeT s t f a = ComposeT { getComposeT :: s (t f) a }Can be useful if you want to layer or nest functor combinators to get both enhancements as a single functor combinator*.
Usually really only useful in the context of other abstractions that expect functor combinators, since this is the best way to turn two functor combinators into a third one.
Interpret
instance (Interpret s f, Interpret t f) => Interpret (ComposeT s t) f interpret @(ComposeT s t) :: (Interpret s f, Interpret t f) => g ~> f -> ComposeT s t g ~> fInterpreting out of these requires the constraints on both layers.
HLift
Origin: Data.HFunctor
Enhancement:
HLift t fletsfexist either unchanged, or with the structure oft.data HLift t f a = HPure (f a) | HOther (t f a)Can be useful if you want to “conditionally enhance”
f. Eitherfcan be enhanced byt, or it can exist in its pure “newly-injected” form.If
tisIdentity, we getEnvT Any, orf :+: f: the “pure or impure” combinator.Interpret
instance Interpret t f => Interpret (HLift t) f interpret @(HLift t) :: Interpret t f => g ~> f -> HLift t g ~> fInterpreting out of these requires the constraint on
t, to handle theHOthercase.
HFree
Origin: Data.HFunctor
Enhancement:
HFree t fletsfexist either unchanged, or with multiple nested enhancements byt.data HFree t f a = HReturn (f a) | HJoin (t (HFree t f) a)It is related to
HLift, but lets you lift over arbitrary many compositions oft, enhancingfmultiple times. This essentially creates a “tree” oftbranches.One particularly useful functor combinator to use is
MapF. In our earlier examples, if we havedata Command ato represent the structure of a single command line argument parser, we can use
type Commands = MapF String Commandto represent multiple potential named commands, each under a different
Stringargument. WithHFree, we can also use:type CommandTree = HFree (MapF String) Commandto represent nested named commands, where each nested sub-command is descended on by a
Stringkey.For another example,
HFree IdentityTis essentiallyStep.Interpret
instance Interpret t f => Interpret (HFree t) f interpret @(HFree t) :: Interpre t f => g ~> f -> HFree t g ~> fInterpreting out of these requires the constraint on
t, to handle theHJoincase.However, it is probably usually more useful to directly pattern match on
HReturnandHJoinand handle the recursion explicitly.Alternatively, we can also define a recursive folding function (provided in Data.HFunctor) to recursively fold down each branch:
foldHFree :: HFunctor t => (g ~> f) -> (t g ~> f) -> HFree t g ~> fThis can be useful because it allows you to distinguish between the different branches, and also requires no constraint on
g.Applied to the
CommandTreeexample, this becomes:foldHFree @(MapF String) @Command :: Command ~> f -> MapF String ~> f -> CommandTree ~> f
Closing Comments
As I discover more interesting or useful functor combinators (or as the abstractions in functor-combinators change), I will continue to update this post. And, in the upcoming weeks and months I plan to present specific programs I have written (and simple examples of usage) that will help show this design pattern in use within a real program.
For now, I hope you can appreciate this as a reference to help guide your exploration of unique “a la carte” (yet not fixed-point-centric) approach to building your programs! You can jump right into using these tools to build your program today by importing Data.Functor.Combinator or wherever they can be found.
I’d be excited to hear about what programs you are able to write, so please do let me know! You can leave a comment, find me on twitter at @mstk, or find me on freenode irc idling on #haskell as jle` if you want to share, or have any questions.
Special Thanks
I am very humbled to be supported by an amazing community, who make it possible for me to devote time to researching and writing these posts. Very special thanks to my supporter at the “Amazing” level on patreon, Josh Vera! :)
Also a special thanks to Koz Ross, who helped proofread this post as a draft.
On the surface, this functor combinator design pattern might look like it fills a similar space to effects systems and libraries like mtl, polysemy, freer-simple, or fused-effects. However, this design pattern actually exists on a different level.
Functor combinator design patterns can be used to help build the structure of the data types and schemas that define your program/DSL. Once you build these nice structures, you then interpret them into some target context. This “target context” is the realm that libraries like mtl and polysemy can fill; functor combinators serve to help you define a structure for your program before you interpret it into whatever Applicative or Monad or effects system you end up using.↩︎