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.Associative

Contents

Description

This module provides tools for working with binary functor combinators that represent interpretable schemas.

These are types HBifunctor t that take two functors f and g and returns a new functor t f g, that "mixes together" f and g in some way.

The high-level usage of this is

biretract :: t f f ~> f

which lets you fully "mix" together the two input functors.

This class also associates each HBifunctor with its "semigroup functor combinator", so we can "squish together" repeated applications of t.

That is, an SF t f a is either:

  • f a
  • t f f a
  • t f (t f f) a
  • t f (t f (t f f)) a
  • .. etc.

which means we can have "list-like" schemas that represent multiple copies of f.

See Data.HBifunctor.Tensor for a version that also provides an analogy to inject, and a more flexible "squished" combinator MF that has an "empty" element.

Synopsis

Associative

class HBifunctor t => Associative t where Source #

An HBifunctor where it doesn't matter which binds first is Associative. Knowing this gives us a lot of power to rearrange the internals of our HFunctor at will.

For example, for the functor product:

data (f :*: g) a = f a :*: g a

We know that f :*: (g :*: h) is the same as (f :*: g) :*: h.

Methods

associating :: (Functor f, Functor g, Functor h) => t f (t g h) <~> t (t f g) h Source #

The isomorphism between t f (t g h) a and t (t f g) h a. To use this isomorphism, see assoc and disassoc.

Instances
Associative Day Source # 
Instance details

Defined in Data.HBifunctor.Associative

Methods

associating :: (Functor f, Functor g, Functor h) => Day f (Day g h) <~> Day (Day f g) h Source #

Associative These1 Source # 
Instance details

Defined in Data.HBifunctor.Associative

Methods

associating :: (Functor f, Functor g, Functor h) => These1 f (These1 g h) <~> These1 (These1 f g) h Source #

Associative Comp Source # 
Instance details

Defined in Data.HBifunctor.Associative

Methods

associating :: (Functor f, Functor g, Functor h) => Comp f (Comp g h) <~> Comp (Comp f g) h Source #

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

Defined in Data.HBifunctor.Associative

Methods

associating :: (Functor f, Functor g, Functor h) => (f :+: (g :+: h)) <~> ((f :+: g) :+: h) Source #

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

Defined in Data.HBifunctor.Associative

Methods

associating :: (Functor f, Functor g, Functor h) => (f :*: (g :*: h)) <~> ((f :*: g) :*: h) Source #

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

Defined in Data.HBifunctor.Associative

Methods

associating :: (Functor f, Functor g, Functor h) => Product f (Product g h) <~> Product (Product f g) h Source #

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

Defined in Data.HBifunctor.Associative

Methods

associating :: (Functor f, Functor g, Functor h) => Sum f (Sum g h) <~> Sum (Sum f g) h Source #

Associative (Joker :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.HBifunctor.Associative

Methods

associating :: (Functor f, Functor g, Functor h) => Joker f (Joker g h) <~> Joker (Joker f g) h Source #

Associative (LeftF :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.HBifunctor.Associative

Methods

associating :: (Functor f, Functor g, Functor h) => LeftF f (LeftF g h) <~> LeftF (LeftF f g) h Source #

Associative (RightF :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.HBifunctor.Associative

Methods

associating :: (Functor f, Functor g, Functor h) => RightF f (RightF g h) <~> RightF (RightF f g) h Source #

Associative (Void3 :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.HBifunctor.Associative

Methods

associating :: (Functor f, Functor g, Functor h) => Void3 f (Void3 g h) <~> Void3 (Void3 f g) h Source #

assoc :: (Associative t, Functor f, Functor g, Functor h) => t f (t g h) ~> t (t f g) h Source #

Reassociate an application of t.

disassoc :: (Associative t, Functor f, Functor g, Functor h) => t (t f g) h ~> t f (t g h) Source #

Reassociate an application of t.

Semigroupoidal

class (Associative t, Interpret (SF t)) => Semigroupoidal t where Source #

For some ts, you can represent the act of applying a functor f to t many times, as a single type. That is, there is some type SF t f that is equivalent to one of:

  • 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

This typeclass associates each t with its "induced semigroupoidal functor combinator" SF t.

This is useful because sometimes you might want to describe a type that can be t f f, t f (t f f), t f (t f (t f f)), etc.; "f applied to itself", with at least one f. This typeclass lets you use a type like NonEmptyF in terms of repeated applications of :*:, or Ap1 in terms of repeated applications of Day, or Free1 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 1, 2, or many different fs that I can use", you can use NonEmptyF f.

At the high level, the main way to use a Semigroupoidal is with biretract and binterpret:

biretract :: t f f ~> f
binterpret :: (f ~> h) -> (g ~> h) -> t f g ~> h

which are like the HBifunctor versions of retract and interpret: they fully "mix" together the two inputs of t.

Also useful is:

toSF :: t f f a -> SF t f a

Which converts a t into its aggregate type SF.

In reality, most Semigroupoidal instances are also Monoidal instances, so you can think of the separation as mostly to help organize functionality. However, there are two non-monoidal semigroupoidal instances of note: LeftF and RightF, which are higher order analogues of the First and Last semigroups, roughly.

Minimal complete definition

appendSF, matchSF

Associated Types

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

The "semigroup functor combinator" generated by t.

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

  • f a
  • t f f a
  • t f (t f f) a
  • t f (t f (t f f)) a
  • t f (t f (t f (t f f))) a
  • .. etc

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

x             ~ NonEmptyF (x :| [])      ~ inject x
x :*: y       ~ NonEmptyF (x :| [y])     ~ toSF (x :*: y)
x :*: y :*: z ~ NonEmptyF (x :| [y,z])
-- etc.

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

Methods

appendSF :: t (SF t f) (SF t f) ~> SF t f Source #

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

matchSF :: Functor f => SF t f ~> (f :+: t f (SF t f)) Source #

consSF :: t f (SF t f) ~> SF t f Source #

Prepend an application of t f to the front of a SF t f.

toSF :: t f f ~> SF t f Source #

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

biretract :: CS t f => t f f ~> f Source #

The HBifunctor analogy of retract. It retracts both fs into a single f, effectively fully mixing them together.

binterpret :: CS t h => (f ~> h) -> (g ~> h) -> t f g ~> h Source #

The HBifunctor analogy of interpret. It takes two interpreting functions, and mixes them together into a target functor h.

Instances
Semigroupoidal Day Source # 
Instance details

Defined in Data.HBifunctor.Associative

Associated Types

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

Methods

appendSF :: Day (SF Day f) (SF Day f) ~> SF Day f Source #

matchSF :: Functor f => SF Day f ~> (f :+: Day f (SF Day f)) Source #

consSF :: Day f (SF Day f) ~> SF Day f Source #

toSF :: Day f f ~> SF Day f Source #

biretract :: CS Day f => Day f f ~> f Source #

binterpret :: CS Day h => (f ~> h) -> (g ~> h) -> Day f g ~> h Source #

Semigroupoidal These1 Source #

Ideally here SF would be equivalent to MF, just like for :+:. This should be possible if we can write a bijection. This bijection should be possible in theory --- but it has not yet been implemented.

Instance details

Defined in Data.HBifunctor.Associative

Associated Types

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

Methods

appendSF :: These1 (SF These1 f) (SF These1 f) ~> SF These1 f Source #

matchSF :: Functor f => SF These1 f ~> (f :+: These1 f (SF These1 f)) Source #

consSF :: These1 f (SF These1 f) ~> SF These1 f Source #

toSF :: These1 f f ~> SF These1 f Source #

biretract :: CS These1 f => These1 f f ~> f Source #

binterpret :: CS These1 h => (f ~> h) -> (g ~> h) -> These1 f g ~> h Source #

Semigroupoidal Comp Source # 
Instance details

Defined in Data.HBifunctor.Associative

Associated Types

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

Methods

appendSF :: Comp (SF Comp f) (SF Comp f) ~> SF Comp f Source #

matchSF :: Functor f => SF Comp f ~> (f :+: Comp f (SF Comp f)) Source #

consSF :: Comp f (SF Comp f) ~> SF Comp f Source #

toSF :: Comp f f ~> SF Comp f Source #

biretract :: CS Comp f => Comp f f ~> f Source #

binterpret :: CS Comp h => (f ~> h) -> (g ~> h) -> Comp f g ~> h Source #

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

Defined in Data.HBifunctor.Associative

Associated Types

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

Methods

appendSF :: (SF (:+:) f :+: SF (:+:) f) ~> SF (:+:) f Source #

matchSF :: Functor f => SF (:+:) f ~> (f :+: (f :+: SF (:+:) f)) Source #

consSF :: (f :+: SF (:+:) f) ~> SF (:+:) f Source #

toSF :: (f :+: f) ~> SF (:+:) f Source #

biretract :: CS (:+:) f => (f :+: f) ~> f Source #

binterpret :: CS (:+:) h => (f ~> h) -> (g ~> h) -> (f :+: g) ~> h Source #

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

Defined in Data.HBifunctor.Associative

Associated Types

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

Methods

appendSF :: (SF (:*:) f :*: SF (:*:) f) ~> SF (:*:) f Source #

matchSF :: Functor f => SF (:*:) f ~> (f :+: (f :*: SF (:*:) f)) Source #

consSF :: (f :*: SF (:*:) f) ~> SF (:*:) f Source #

toSF :: (f :*: f) ~> SF (:*:) f Source #

biretract :: CS (:*:) f => (f :*: f) ~> f Source #

binterpret :: CS (:*:) h => (f ~> h) -> (g ~> h) -> (f :*: g) ~> h Source #

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

Defined in Data.HBifunctor.Associative

Associated Types

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

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

Defined in Data.HBifunctor.Associative

Associated Types

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

Methods

appendSF :: Sum (SF Sum f) (SF Sum f) ~> SF Sum f Source #

matchSF :: Functor f => SF Sum f ~> (f :+: Sum f (SF Sum f)) Source #

consSF :: Sum f (SF Sum f) ~> SF Sum f Source #

toSF :: Sum f f ~> SF Sum f Source #

biretract :: CS Sum f => Sum f f ~> f Source #

binterpret :: CS Sum h => (f ~> h) -> (g ~> h) -> Sum f g ~> h Source #

Semigroupoidal (Joker :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.HBifunctor.Associative

Associated Types

type SF Joker :: (Type -> Type) -> Type -> Type Source #

Methods

appendSF :: Joker (SF Joker f) (SF Joker f) ~> SF Joker f Source #

matchSF :: Functor f => SF Joker f ~> (f :+: Joker f (SF Joker f)) Source #

consSF :: Joker f (SF Joker f) ~> SF Joker f Source #

toSF :: Joker f f ~> SF Joker f Source #

biretract :: CS Joker f => Joker f f ~> f Source #

binterpret :: CS Joker h => (f ~> h) -> (g ~> h) -> Joker f g ~> h Source #

Semigroupoidal (LeftF :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.HBifunctor.Associative

Associated Types

type SF LeftF :: (Type -> Type) -> Type -> Type Source #

Methods

appendSF :: LeftF (SF LeftF f) (SF LeftF f) ~> SF LeftF f Source #

matchSF :: Functor f => SF LeftF f ~> (f :+: LeftF f (SF LeftF f)) Source #

consSF :: LeftF f (SF LeftF f) ~> SF LeftF f Source #

toSF :: LeftF f f ~> SF LeftF f Source #

biretract :: CS LeftF f => LeftF f f ~> f Source #

binterpret :: CS LeftF h => (f ~> h) -> (g ~> h) -> LeftF f g ~> h Source #

Semigroupoidal (RightF :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.HBifunctor.Associative

Associated Types

type SF RightF :: (Type -> Type) -> Type -> Type Source #

Methods

appendSF :: RightF (SF RightF f) (SF RightF f) ~> SF RightF f Source #

matchSF :: Functor f => SF RightF f ~> (f :+: RightF f (SF RightF f)) Source #

consSF :: RightF f (SF RightF f) ~> SF RightF f Source #

toSF :: RightF f f ~> SF RightF f Source #

biretract :: CS RightF f => RightF f f ~> f Source #

binterpret :: CS RightF h => (f ~> h) -> (g ~> h) -> RightF f g ~> h Source #

type CS t = C (SF t) Source #

Convenient alias for the constraint required for biretract, binterpret, etc.

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

matchingSF :: (Semigroupoidal t, Functor f) => SF t f <~> (f :+: t f (SF t f)) Source #

An SF t f represents the successive application of t to f, over and over again. So, that means that an SF t f must either be a single f, or an t f (SF t f).

matchingSF states that these two are isomorphic. Use matchSF and inject !*! consSF to convert between one and the other.

Utility

biget :: (Semigroupoidal t, CS t (Const b)) => (forall x. f x -> b) -> (forall x. g x -> b) -> t f g a -> b Source #

Useful wrapper over binterpret to allow you to directly extract a value b out of the t f a, if you can convert f x into b.

Note that depending on the constraints on the interpretation of t, you may have extra constraints on b.

For some constraints (like Monad), this will not be usable.

-- Return the length of either the list, or the Map, depending on which
--   one s in the +
biget length length
    :: ([] :+: Map Int) Char
    -> Int

-- Return the length of both the list and the map, added together
biget (Sum . length) (Sum . length)
    :: Day [] (Map Int) Char
    -> Sum Int

bicollect :: (Semigroupoidal t, CS t (Const [b])) => (forall x. f x -> b) -> (forall x. g x -> b) -> t f g a -> [b] Source #

Useful wrapper over biget to allow you to collect a b from all instances of f and g inside a t f g a.

This will work if C t is Unconstrained, Apply, or Applicative.

(!*!) :: (Semigroupoidal t, CS t h) => (f ~> h) -> (g ~> h) -> t f g ~> h infixr 5 Source #

Infix alias for binterpret

(!$!) :: (Semigroupoidal t, CS t (Const b)) => (forall x. f x -> b) -> (forall x. g x -> b) -> t f g a -> b infixr 5 Source #

Infix alias for biget

-- Return the length of either the list, or the Map, depending on which
--   one s in the +
length !$! length
    :: ([] :+: Map Int) Char
    -> Int

-- Return the length of both the list and the map, added together
Sum . length !$! Sum . length
    :: Day [] (Map Int) Char
    -> Sum Int