| Copyright | (c) Justin Le 2019 |
|---|---|
| License | BSD3 |
| Maintainer | justin@jle.im |
| Stability | experimental |
| Portability | non-portable |
| Safe Haskell | None |
| Language | Haskell2010 |
Data.HBifunctor.Associative
Contents
Description
This module provides tools for working with binary functor combinators that represent interpretable schemas.
These are types that take two functors HBifunctor tf 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 is either:SF t f a
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
- class HBifunctor t => Associative t where
- associating :: (Functor f, Functor g, Functor h) => t f (t g h) <~> t (t f g) h
- assoc :: (Associative t, Functor f, Functor g, Functor h) => t f (t g h) ~> t (t f g) h
- disassoc :: (Associative t, Functor f, Functor g, Functor h) => t (t f g) h ~> t f (t g h)
- class (Associative t, Interpret (SF t)) => Semigroupoidal t where
- type CS t = C (SF t)
- matchingSF :: (Semigroupoidal t, Functor f) => SF t f <~> (f :+: t f (SF t f))
- biget :: (Semigroupoidal t, CS t (Const b)) => (forall x. f x -> b) -> (forall x. g x -> b) -> t f g a -> b
- bicollect :: (Semigroupoidal t, CS t (Const [b])) => (forall x. f x -> b) -> (forall x. g x -> b) -> t f g a -> [b]
- (!*!) :: (Semigroupoidal t, CS t h) => (f ~> h) -> (g ~> h) -> t f g ~> h
- (!$!) :: (Semigroupoidal t, CS t (Const b)) => (forall x. f x -> b) -> (forall x. g x -> b) -> t f g a -> b
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.
Instances
| Associative Day Source # | |
| Associative These1 Source # | |
| Associative Comp Source # | |
| Associative ((:+:) :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Source # | |
| Associative ((:*:) :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Source # | |
| Associative (Product :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Source # | |
| Associative (Sum :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Source # | |
| Associative (Joker :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Source # | |
| Associative (LeftF :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Source # | |
| Associative (RightF :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Source # | |
| Associative (Void3 :: (Type -> Type) -> (Type -> Type) -> Type -> Type) 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 that is equivalent to one of:SF
t f
f a-- 1 timet f f a-- 2 timest f (t f f) a-- 3 timest f (t f (t f f)) a-- 4 timest 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 can be interpreted as "a free selection of two
:*: ffs", 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~>fbinterpret:: (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.
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:|[]) ~injectx 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 represents multiple applications of SF t ft f to
itself, then we can also "append" two s applied to
themselves into one giant SF t f containing all of the SF t ft 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
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 #
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.
- If
isC(SFt)Unconstrained, there are no constraints onb - If
isC(SFt)Apply,bneeds to be an instance ofSemigroup - If
isC(SFt)Applicative,bneeds to be an instance ofMonoid
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+bigetlengthlength :: ([] :+:MapInt)Char-> Int -- Return the length of both the list and the map, added togetherbiget(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 is C tUnconstrained,
Apply, or Applicative.
(!*!) :: (Semigroupoidal t, CS t h) => (f ~> h) -> (g ~> h) -> t f g ~> h infixr 5 Source #
Infix alias for binterpret