functor-combinators-0.3.6.0: Tools for functor combinator-based program design
Copyright(c) Justin Le 2019
LicenseBSD3
Maintainerjustin@jle.im
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

Data.HBifunctor.Tensor

Description

This module provides tools for working with binary functor combinators.

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

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

Tensor gives some extra properties of your binary functor combinator: associativity and identity (see docs for Tensor for more details).

The binary analog of Interpret is MonoidIn. If your combinator t and target functor f is an instance of MonoidIn t f, it means you can "interpret" out of your tensored values, and also "generate" values of f.

biretract :: (f :+: f) a -> f a
pureT     :: V1 a -> f a

biretract :: Plus f => (f :*: f) a -> f a
pureT     :: Plus f => Proxy a -> f a

biretract :: Applicative f => Day f f a -> f a
pureT     :: Applicative f => Identity a -> f a

biretract :: Monad f => Comp f f a -> f a
pureT     :: Monad f => Identity a -> f a
Synopsis

Tensor

class (Associative t, Inject (ListBy t)) => Tensor t i | t -> i where Source #

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

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

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

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

Formally, we can say that t enriches a the category of endofunctors with monoid strcture: it turns our endofunctor category into a "monoidal category".

Different instances of t each enrich the endofunctor category in different ways, giving a different monoidal category.

Minimal complete definition

intro1, intro2, elim1, elim2, appendLB, splitNE, splittingLB

Associated Types

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

The "monoidal functor combinator" induced by t.

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

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

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

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

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

See NonEmptyBy for a "non-empty" version of this type.

Methods

intro1 :: f ~> t f i Source #

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

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

intro2 :: g ~> t i g Source #

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

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

elim1 :: FunctorBy t f => t f i ~> f Source #

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

elim2 :: FunctorBy t g => t i g ~> g Source #

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

appendLB :: t (ListBy t f) (ListBy t f) ~> ListBy t f Source #

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

Note that this essentially gives an instance for SemigroupIn t (ListBy t f), for any functor f; this is witnessed by WrapLB.

splitNE :: NonEmptyBy t f ~> t f (ListBy t f) Source #

Lets you convert an NonEmptyBy t f into a single application of f to ListBy t f.

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

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

splittingLB :: ListBy t f <~> (i :+: t f (ListBy t f)) Source #

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

To use this property, see nilLB, consLB, and unconsLB.

toListBy :: t f f ~> ListBy t f Source #

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

fromNE :: NonEmptyBy t f ~> ListBy t f Source #

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

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

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

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

Instances

Instances details
Tensor Day Identity Source # 
Instance details

Defined in Data.HBifunctor.Tensor

Associated Types

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

Methods

intro1 :: forall (f :: Type -> Type). f ~> Day f Identity Source #

intro2 :: forall (g :: Type -> Type). g ~> Day Identity g Source #

elim1 :: forall (f :: Type -> Type). FunctorBy Day f => Day f Identity ~> f Source #

elim2 :: forall (g :: Type -> Type). FunctorBy Day g => Day Identity g ~> g Source #

appendLB :: forall (f :: Type -> Type). Day (ListBy Day f) (ListBy Day f) ~> ListBy Day f Source #

splitNE :: forall (f :: Type -> Type). NonEmptyBy Day f ~> Day f (ListBy Day f) Source #

splittingLB :: forall (f :: Type -> Type). ListBy Day f <~> (Identity :+: Day f (ListBy Day f)) Source #

toListBy :: forall (f :: Type -> Type). Day f f ~> ListBy Day f Source #

fromNE :: forall (f :: Type -> Type). NonEmptyBy Day f ~> ListBy Day f Source #

Tensor Day Identity Source # 
Instance details

Defined in Data.HBifunctor.Tensor

Associated Types

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

Methods

intro1 :: forall (f :: Type -> Type). f ~> Day f Identity Source #

intro2 :: forall (g :: Type -> Type). g ~> Day Identity g Source #

elim1 :: forall (f :: Type -> Type). FunctorBy Day f => Day f Identity ~> f Source #

elim2 :: forall (g :: Type -> Type). FunctorBy Day g => Day Identity g ~> g Source #

appendLB :: forall (f :: Type -> Type). Day (ListBy Day f) (ListBy Day f) ~> ListBy Day f Source #

splitNE :: forall (f :: Type -> Type). NonEmptyBy Day f ~> Day f (ListBy Day f) Source #

splittingLB :: forall (f :: Type -> Type). ListBy Day f <~> (Identity :+: Day f (ListBy Day f)) Source #

toListBy :: forall (f :: Type -> Type). Day f f ~> ListBy Day f Source #

fromNE :: forall (f :: Type -> Type). NonEmptyBy Day f ~> ListBy Day f Source #

Tensor Night Not Source #

Since: 0.3.0.0

Instance details

Defined in Data.HBifunctor.Tensor

Associated Types

type ListBy Night :: (Type -> Type) -> Type -> Type Source #

Methods

intro1 :: forall (f :: Type -> Type). f ~> Night f Not Source #

intro2 :: forall (g :: Type -> Type). g ~> Night Not g Source #

elim1 :: forall (f :: Type -> Type). FunctorBy Night f => Night f Not ~> f Source #

elim2 :: forall (g :: Type -> Type). FunctorBy Night g => Night Not g ~> g Source #

appendLB :: forall (f :: Type -> Type). Night (ListBy Night f) (ListBy Night f) ~> ListBy Night f Source #

splitNE :: forall (f :: Type -> Type). NonEmptyBy Night f ~> Night f (ListBy Night f) Source #

splittingLB :: forall (f :: Type -> Type). ListBy Night f <~> (Not :+: Night f (ListBy Night f)) Source #

toListBy :: forall (f :: Type -> Type). Night f f ~> ListBy Night f Source #

fromNE :: forall (f :: Type -> Type). NonEmptyBy Night f ~> ListBy Night f Source #

Tensor Night Not Source # 
Instance details

Defined in Data.HBifunctor.Tensor

Associated Types

type ListBy Night :: (Type -> Type) -> Type -> Type Source #

Methods

intro1 :: forall (f :: Type -> Type). f ~> Night f Not Source #

intro2 :: forall (g :: Type -> Type). g ~> Night Not g Source #

elim1 :: forall (f :: Type -> Type). FunctorBy Night f => Night f Not ~> f Source #

elim2 :: forall (g :: Type -> Type). FunctorBy Night g => Night Not g ~> g Source #

appendLB :: forall (f :: Type -> Type). Night (ListBy Night f) (ListBy Night f) ~> ListBy Night f Source #

splitNE :: forall (f :: Type -> Type). NonEmptyBy Night f ~> Night f (ListBy Night f) Source #

splittingLB :: forall (f :: Type -> Type). ListBy Night f <~> (Not :+: Night f (ListBy Night f)) Source #

toListBy :: forall (f :: Type -> Type). Night f f ~> ListBy Night f Source #

fromNE :: forall (f :: Type -> Type). NonEmptyBy Night f ~> ListBy Night f Source #

Tensor Day (Proxy :: Type -> Type) Source #

Since: 0.3.0.0

Instance details

Defined in Data.HBifunctor.Tensor

Associated Types

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

Methods

intro1 :: forall (f :: Type -> Type). f ~> Day f Proxy Source #

intro2 :: forall (g :: Type -> Type). g ~> Day Proxy g Source #

elim1 :: forall (f :: Type -> Type). FunctorBy Day f => Day f Proxy ~> f Source #

elim2 :: forall (g :: Type -> Type). FunctorBy Day g => Day Proxy g ~> g Source #

appendLB :: forall (f :: Type -> Type). Day (ListBy Day f) (ListBy Day f) ~> ListBy Day f Source #

splitNE :: forall (f :: Type -> Type). NonEmptyBy Day f ~> Day f (ListBy Day f) Source #

splittingLB :: forall (f :: Type -> Type). ListBy Day f <~> (Proxy :+: Day f (ListBy Day f)) Source #

toListBy :: forall (f :: Type -> Type). Day f f ~> ListBy Day f Source #

fromNE :: forall (f :: Type -> Type). NonEmptyBy Day f ~> ListBy Day f Source #

Tensor These1 (V1 :: Type -> Type) Source # 
Instance details

Defined in Data.HBifunctor.Tensor

Associated Types

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

Methods

intro1 :: forall (f :: Type -> Type). f ~> These1 f V1 Source #

intro2 :: forall (g :: Type -> Type). g ~> These1 V1 g Source #

elim1 :: forall (f :: Type -> Type). FunctorBy These1 f => These1 f V1 ~> f Source #

elim2 :: forall (g :: Type -> Type). FunctorBy These1 g => These1 V1 g ~> g Source #

appendLB :: forall (f :: Type -> Type). These1 (ListBy These1 f) (ListBy These1 f) ~> ListBy These1 f Source #

splitNE :: forall (f :: Type -> Type). NonEmptyBy These1 f ~> These1 f (ListBy These1 f) Source #

splittingLB :: forall (f :: Type -> Type). ListBy These1 f <~> (V1 :+: These1 f (ListBy These1 f)) Source #

toListBy :: forall (f :: Type -> Type). These1 f f ~> ListBy These1 f Source #

fromNE :: forall (f :: Type -> Type). NonEmptyBy These1 f ~> ListBy These1 f Source #

Tensor (Comp :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Identity Source # 
Instance details

Defined in Data.HBifunctor.Tensor

Associated Types

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

Methods

intro1 :: forall (f :: Type -> Type). f ~> Comp f Identity Source #

intro2 :: forall (g :: Type -> Type). g ~> Comp Identity g Source #

elim1 :: forall (f :: Type -> Type). FunctorBy Comp f => Comp f Identity ~> f Source #

elim2 :: forall (g :: Type -> Type). FunctorBy Comp g => Comp Identity g ~> g Source #

appendLB :: forall (f :: Type -> Type). Comp (ListBy Comp f) (ListBy Comp f) ~> ListBy Comp f Source #

splitNE :: forall (f :: Type -> Type). NonEmptyBy Comp f ~> Comp f (ListBy Comp f) Source #

splittingLB :: forall (f :: Type -> Type). ListBy Comp f <~> (Identity :+: Comp f (ListBy Comp f)) Source #

toListBy :: forall (f :: Type -> Type). Comp f f ~> ListBy Comp f Source #

fromNE :: forall (f :: Type -> Type). NonEmptyBy Comp f ~> ListBy Comp f Source #

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

Defined in Data.HBifunctor.Tensor

Associated Types

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

Methods

intro1 :: forall (f :: Type -> Type). f ~> (f :+: V1) Source #

intro2 :: forall (g :: Type -> Type). g ~> (V1 :+: g) Source #

elim1 :: forall (f :: Type -> Type). FunctorBy (:+:) f => (f :+: V1) ~> f Source #

elim2 :: forall (g :: Type -> Type). FunctorBy (:+:) g => (V1 :+: g) ~> g Source #

appendLB :: forall (f :: Type -> Type). (ListBy (:+:) f :+: ListBy (:+:) f) ~> ListBy (:+:) f Source #

splitNE :: forall (f :: Type -> Type). NonEmptyBy (:+:) f ~> (f :+: ListBy (:+:) f) Source #

splittingLB :: forall (f :: Type -> Type). ListBy (:+:) f <~> (V1 :+: (f :+: ListBy (:+:) f)) Source #

toListBy :: forall (f :: Type -> Type). (f :+: f) ~> ListBy (:+:) f Source #

fromNE :: forall (f :: Type -> Type). NonEmptyBy (:+:) f ~> ListBy (:+:) f Source #

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

Defined in Data.HBifunctor.Tensor

Associated Types

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

Methods

intro1 :: forall (f :: Type -> Type). f ~> (f :*: Proxy) Source #

intro2 :: forall (g :: Type -> Type). g ~> (Proxy :*: g) Source #

elim1 :: forall (f :: Type -> Type). FunctorBy (:*:) f => (f :*: Proxy) ~> f Source #

elim2 :: forall (g :: Type -> Type). FunctorBy (:*:) g => (Proxy :*: g) ~> g Source #

appendLB :: forall (f :: Type -> Type). (ListBy (:*:) f :*: ListBy (:*:) f) ~> ListBy (:*:) f Source #

splitNE :: forall (f :: Type -> Type). NonEmptyBy (:*:) f ~> (f :*: ListBy (:*:) f) Source #

splittingLB :: forall (f :: Type -> Type). ListBy (:*:) f <~> (Proxy :+: (f :*: ListBy (:*:) f)) Source #

toListBy :: forall (f :: Type -> Type). (f :*: f) ~> ListBy (:*:) f Source #

fromNE :: forall (f :: Type -> Type). NonEmptyBy (:*:) f ~> ListBy (:*:) f Source #

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

Defined in Data.HBifunctor.Tensor

Associated Types

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

Methods

intro1 :: forall (f :: Type -> Type). f ~> Product f Proxy Source #

intro2 :: forall (g :: Type -> Type). g ~> Product Proxy g Source #

elim1 :: forall (f :: Type -> Type). FunctorBy Product f => Product f Proxy ~> f Source #

elim2 :: forall (g :: Type -> Type). FunctorBy Product g => Product Proxy g ~> g Source #

appendLB :: forall (f :: Type -> Type). Product (ListBy Product f) (ListBy Product f) ~> ListBy Product f Source #

splitNE :: forall (f :: Type -> Type). NonEmptyBy Product f ~> Product f (ListBy Product f) Source #

splittingLB :: forall (f :: Type -> Type). ListBy Product f <~> (Proxy :+: Product f (ListBy Product f)) Source #

toListBy :: forall (f :: Type -> Type). Product f f ~> ListBy Product f Source #

fromNE :: forall (f :: Type -> Type). NonEmptyBy Product f ~> ListBy Product f Source #

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

Defined in Data.HBifunctor.Tensor

Associated Types

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

Methods

intro1 :: forall (f :: Type -> Type). f ~> Sum f V1 Source #

intro2 :: forall (g :: Type -> Type). g ~> Sum V1 g Source #

elim1 :: forall (f :: Type -> Type). FunctorBy Sum f => Sum f V1 ~> f Source #

elim2 :: forall (g :: Type -> Type). FunctorBy Sum g => Sum V1 g ~> g Source #

appendLB :: forall (f :: Type -> Type). Sum (ListBy Sum f) (ListBy Sum f) ~> ListBy Sum f Source #

splitNE :: forall (f :: Type -> Type). NonEmptyBy Sum f ~> Sum f (ListBy Sum f) Source #

splittingLB :: forall (f :: Type -> Type). ListBy Sum f <~> (V1 :+: Sum f (ListBy Sum f)) Source #

toListBy :: forall (f :: Type -> Type). Sum f f ~> ListBy Sum f Source #

fromNE :: forall (f :: Type -> Type). NonEmptyBy Sum f ~> ListBy Sum f Source #

Tensor t i => Tensor (WrapHBF t) (WrapF i) Source # 
Instance details

Defined in Data.HBifunctor.Tensor

Associated Types

type ListBy (WrapHBF t) :: (Type -> Type) -> Type -> Type Source #

Methods

intro1 :: forall (f :: Type -> Type). f ~> WrapHBF t f (WrapF i) Source #

intro2 :: forall (g :: Type -> Type). g ~> WrapHBF t (WrapF i) g Source #

elim1 :: forall (f :: Type -> Type). FunctorBy (WrapHBF t) f => WrapHBF t f (WrapF i) ~> f Source #

elim2 :: forall (g :: Type -> Type). FunctorBy (WrapHBF t) g => WrapHBF t (WrapF i) g ~> g Source #

appendLB :: forall (f :: Type -> Type). WrapHBF t (ListBy (WrapHBF t) f) (ListBy (WrapHBF t) f) ~> ListBy (WrapHBF t) f Source #

splitNE :: forall (f :: Type -> Type). NonEmptyBy (WrapHBF t) f ~> WrapHBF t f (ListBy (WrapHBF t) f) Source #

splittingLB :: forall (f :: Type -> Type). ListBy (WrapHBF t) f <~> (WrapF i :+: WrapHBF t f (ListBy (WrapHBF t) f)) Source #

toListBy :: forall (f :: Type -> Type). WrapHBF t f f ~> ListBy (WrapHBF t) f Source #

fromNE :: forall (f :: Type -> Type). NonEmptyBy (WrapHBF t) f ~> ListBy (WrapHBF t) f Source #

rightIdentity :: (Tensor t i, FunctorBy t f) => f <~> t f i Source #

f is isomorphic to t f i: that is, i is the identity of t, and leaves f unchanged.

leftIdentity :: (Tensor t i, FunctorBy t g) => g <~> t i g Source #

g is isomorphic to t i g: that is, i is the identity of t, and leaves g unchanged.

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

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

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

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

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

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

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

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

MonoidIn

class (Tensor t i, SemigroupIn t f) => MonoidIn t i f where Source #

This class effectively gives us a way to generate a value of f a based on an i a, for Tensor t i. Having this ability makes a lot of interesting functions possible when used with biretract from SemigroupIn that weren't possible without it: it gives us a "base case" for recursion in a lot of cases.

Essentially, we get an i ~> f, pureT, where we can introduce an f a as long as we have an i a.

Formally, if we have Tensor t i, we are enriching the category of endofunctors with monoid structure, turning it into a monoidal category. Different choices of t give different monoidal categories.

A functor f is known as a "monoid in the (monoidal) category of endofunctors on t" if we can biretract:

t f f ~> f

and also pureT:

i ~> f

This gives us a few interesting results in category theory, which you can stil reading about if you don't care:

  • All functors are monoids in the monoidal category on :+:
  • The class of functors that are monoids in the monoidal category on :*: is exactly the functors that are instances of Plus.
  • The class of functors that are monoids in the monoidal category on Day is exactly the functors that are instances of Applicative.
  • The class of functors that are monoids in the monoidal category on Comp is exactly the functors that are instances of Monad.

This is the meaning behind the common adage, "monads are just monoids in the category of endofunctors". It means that if you enrich the category of endofunctors to be monoidal with Comp, then the class of functors that are monoids in that monoidal category are exactly what monads are. However, the adage is a little misleading: there are many other ways to enrich the category of endofunctors to be monoidal, and Comp is just one of them. Similarly, the class of functors that are monoids in the category of endofunctors enriched by Day are Applicative.

Note that instances of this class are intended to be written with t and i to be fixed type constructors, and f to be allowed to vary freely:

instance Monad f => MonoidIn Comp Identity f

Any other sort of instance and it's easy to run into problems with type inference. If you want to write an instance that's "polymorphic" on tensor choice, use the WrapHBF and WrapF newtype wrappers over type variables, where the third argument also uses a type constructor:

instance MonoidIn (WrapHBF t) (WrapF i) (MyFunctor t i)

This will prevent problems with overloaded instances.

Minimal complete definition

Nothing

Methods

pureT :: i ~> f Source #

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

Specialized (and simplified), this type is:

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

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

Along with biretract, this function makes f a monoid in the category of endofunctors with respect to tensor t.

default pureT :: Interpret (ListBy t) f => i ~> f Source #

Instances

Instances details
(Apply f, Applicative f) => MonoidIn Day Identity f Source #

Instances of Applicative are monoids in the monoidal category on the covariant Day.

Note that because of typeclass constraints, this requires Apply as well as Applicative. But, you can get a "local" instance of Apply for any Applicative using unsafeApply.

Instance details

Defined in Data.HBifunctor.Tensor

Methods

pureT :: Identity ~> f Source #

Conclude f => MonoidIn Night Not f Source #

Instances of Conclude are monoids in the monoidal category on Night.

Instance details

Defined in Data.HBifunctor.Tensor

Methods

pureT :: Not ~> f Source #

(Divise f, Divisible f) => MonoidIn Day (Proxy :: Type -> Type) f Source #

Instances of Divisible are monoids in the monoidal category on contravariant Day.

Note that because of typeclass constraints, this requires Divise as well as Divisible. But, you can get a "local" instance of Divise for any Divisible using unsafeDivise.

Since: 0.3.0.0

Instance details

Defined in Data.HBifunctor.Tensor

Methods

pureT :: Proxy ~> f Source #

Alt f => MonoidIn These1 (V1 :: Type -> Type) f Source # 
Instance details

Defined in Data.HBifunctor.Tensor

Methods

pureT :: V1 ~> f Source #

(Bind f, Monad f) => MonoidIn (Comp :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Identity f Source #

Instances of Monad are monoids in the monoidal category on Comp.

This instance is the "proof" that "monads are the monoids in the category of endofunctors (enriched with Comp)"

Note that because of typeclass constraints, this requires Bind as well as Monad. But, you can get a "local" instance of Apply for any Monad using unsafeBind.

Instance details

Defined in Data.HBifunctor.Tensor

Methods

pureT :: Identity ~> f Source #

MonoidIn ((:+:) :: (Type -> Type) -> (Type -> Type) -> Type -> Type) (V1 :: Type -> Type) f Source #

All functors are monoids in the monoidal category on :+:.

Instance details

Defined in Data.HBifunctor.Tensor

Methods

pureT :: V1 ~> f Source #

Plus f => MonoidIn ((:*:) :: (Type -> Type) -> (Type -> Type) -> Type -> Type) (Proxy :: Type -> Type) f Source #

Instances of Plus are monoids in the monoidal category on :*:.

Instance details

Defined in Data.HBifunctor.Tensor

Methods

pureT :: Proxy ~> f Source #

Plus f => MonoidIn (Product :: (Type -> Type) -> (Type -> Type) -> Type -> Type) (Proxy :: Type -> Type) f Source #

Instances of Plus are monoids in the monoidal category on Product.

Instance details

Defined in Data.HBifunctor.Tensor

Methods

pureT :: Proxy ~> f Source #

MonoidIn (Sum :: (Type -> Type) -> (Type -> Type) -> Type -> Type) (V1 :: Type -> Type) f Source #

All functors are monoids in the monoidal category on Sum.

Instance details

Defined in Data.HBifunctor.Tensor

Methods

pureT :: V1 ~> f Source #

(Tensor t i, FunctorBy t f, FunctorBy t (WrapLB t f)) => MonoidIn (WrapHBF t) (WrapF i) (WrapLB t f) Source # 
Instance details

Defined in Data.HBifunctor.Tensor

Methods

pureT :: WrapF i ~> WrapLB t f Source #

(Tensor t i, FunctorBy t (Chain t i f)) => MonoidIn (WrapHBF t) (WrapF i) (Chain t i f) Source #

Chain t i is the "free MonoidIn t i". However, we have to wrap t in WrapHBF and i in WrapF to prevent overlapping instances.

Instance details

Defined in Data.HFunctor.Chain

Methods

pureT :: WrapF i ~> Chain t i f Source #

nilLB :: forall t i f. Tensor t i => i ~> ListBy t f Source #

Create the "empty ListBy".

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

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

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

Note that this essentially gives an instance for MonoidIn t i (ListBy t f), for any functor f; this is witnessed by WrapLB.

consLB :: Tensor t i => t f (ListBy t f) ~> ListBy t f Source #

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

unconsLB :: Tensor t i => ListBy t f ~> (i :+: t f (ListBy t f)) Source #

"Pattern match" on an ListBy t

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

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

retractLB :: forall t i f. MonoidIn t i f => ListBy t f ~> f Source #

An implementation of retract that works for any instance of MonoidIn t i for ListBy t.

Can be useful as a default implementation if you already have MonoidIn implemented.

interpretLB :: forall t i g f. MonoidIn t i f => (g ~> f) -> ListBy t g ~> f Source #

An implementation of interpret that works for any instance of MonoidIn t i for ListBy t.

Can be useful as a default implementation if you already have MonoidIn implemented.

Utility

inL :: forall t i f g. MonoidIn t i g => f ~> t f g Source #

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

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

inR :: forall t i f g. MonoidIn t i f => g ~> t f g Source #

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

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

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

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

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

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

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

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

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

A poly-kinded version of outL for :*:.

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

A poly-kinded version of outR for :*:.

newtype WrapF f a Source #

A newtype wrapper meant to be used to define polymorphic MonoidIn instances. See documentation for MonoidIn for more information.

Please do not ever define an instance of MonoidIn "naked" on the third parameter:

instance MonidIn (WrapHBF t) (WrapF i) f

As that would globally ruin everything using WrapHBF.

Constructors

WrapF 

Fields

Instances

Instances details
Functor f => Functor (WrapF f) Source # 
Instance details

Defined in Data.HBifunctor.Tensor

Methods

fmap :: (a -> b) -> WrapF f a -> WrapF f b #

(<$) :: a -> WrapF f b -> WrapF f a #

Foldable f => Foldable (WrapF f) Source # 
Instance details

Defined in Data.HBifunctor.Tensor

Methods

fold :: Monoid m => WrapF f m -> m #

foldMap :: Monoid m => (a -> m) -> WrapF f a -> m #

foldMap' :: Monoid m => (a -> m) -> WrapF f a -> m #

foldr :: (a -> b -> b) -> b -> WrapF f a -> b #

foldr' :: (a -> b -> b) -> b -> WrapF f a -> b #

foldl :: (b -> a -> b) -> b -> WrapF f a -> b #

foldl' :: (b -> a -> b) -> b -> WrapF f a -> b #

foldr1 :: (a -> a -> a) -> WrapF f a -> a #

foldl1 :: (a -> a -> a) -> WrapF f a -> a #

toList :: WrapF f a -> [a] #

null :: WrapF f a -> Bool #

length :: WrapF f a -> Int #

elem :: Eq a => a -> WrapF f a -> Bool #

maximum :: Ord a => WrapF f a -> a #

minimum :: Ord a => WrapF f a -> a #

sum :: Num a => WrapF f a -> a #

product :: Num a => WrapF f a -> a #

Traversable f => Traversable (WrapF f) Source # 
Instance details

Defined in Data.HBifunctor.Tensor

Methods

traverse :: Applicative f0 => (a -> f0 b) -> WrapF f a -> f0 (WrapF f b) #

sequenceA :: Applicative f0 => WrapF f (f0 a) -> f0 (WrapF f a) #

mapM :: Monad m => (a -> m b) -> WrapF f a -> m (WrapF f b) #

sequence :: Monad m => WrapF f (m a) -> m (WrapF f a) #

Eq1 f => Eq1 (WrapF f) Source # 
Instance details

Defined in Data.HBifunctor.Tensor

Methods

liftEq :: (a -> b -> Bool) -> WrapF f a -> WrapF f b -> Bool #

Ord1 f => Ord1 (WrapF f) Source # 
Instance details

Defined in Data.HBifunctor.Tensor

Methods

liftCompare :: (a -> b -> Ordering) -> WrapF f a -> WrapF f b -> Ordering #

Show1 f => Show1 (WrapF f) Source # 
Instance details

Defined in Data.HBifunctor.Tensor

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> WrapF f a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [WrapF f a] -> ShowS #

Eq (f a) => Eq (WrapF f a) Source # 
Instance details

Defined in Data.HBifunctor.Tensor

Methods

(==) :: WrapF f a -> WrapF f a -> Bool #

(/=) :: WrapF f a -> WrapF f a -> Bool #

(Typeable a, Typeable f, Typeable k, Data (f a)) => Data (WrapF f a) Source # 
Instance details

Defined in Data.HBifunctor.Tensor

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> WrapF f a -> c (WrapF f a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (WrapF f a) #

toConstr :: WrapF f a -> Constr #

dataTypeOf :: WrapF f a -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (WrapF f a)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (WrapF f a)) #

gmapT :: (forall b. Data b => b -> b) -> WrapF f a -> WrapF f a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> WrapF f a -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> WrapF f a -> r #

gmapQ :: (forall d. Data d => d -> u) -> WrapF f a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> WrapF f a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> WrapF f a -> m (WrapF f a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> WrapF f a -> m (WrapF f a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> WrapF f a -> m (WrapF f a) #

Ord (f a) => Ord (WrapF f a) Source # 
Instance details

Defined in Data.HBifunctor.Tensor

Methods

compare :: WrapF f a -> WrapF f a -> Ordering #

(<) :: WrapF f a -> WrapF f a -> Bool #

(<=) :: WrapF f a -> WrapF f a -> Bool #

(>) :: WrapF f a -> WrapF f a -> Bool #

(>=) :: WrapF f a -> WrapF f a -> Bool #

max :: WrapF f a -> WrapF f a -> WrapF f a #

min :: WrapF f a -> WrapF f a -> WrapF f a #

Read (f a) => Read (WrapF f a) Source # 
Instance details

Defined in Data.HBifunctor.Tensor

Show (f a) => Show (WrapF f a) Source # 
Instance details

Defined in Data.HBifunctor.Tensor

Methods

showsPrec :: Int -> WrapF f a -> ShowS #

show :: WrapF f a -> String #

showList :: [WrapF f a] -> ShowS #

Generic (WrapF f a) Source # 
Instance details

Defined in Data.HBifunctor.Tensor

Associated Types

type Rep (WrapF f a) :: Type -> Type #

Methods

from :: WrapF f a -> Rep (WrapF f a) x #

to :: Rep (WrapF f a) x -> WrapF f a #

Tensor t i => Tensor (WrapHBF t) (WrapF i) Source # 
Instance details

Defined in Data.HBifunctor.Tensor

Associated Types

type ListBy (WrapHBF t) :: (Type -> Type) -> Type -> Type Source #

Methods

intro1 :: forall (f :: Type -> Type). f ~> WrapHBF t f (WrapF i) Source #

intro2 :: forall (g :: Type -> Type). g ~> WrapHBF t (WrapF i) g Source #

elim1 :: forall (f :: Type -> Type). FunctorBy (WrapHBF t) f => WrapHBF t f (WrapF i) ~> f Source #

elim2 :: forall (g :: Type -> Type). FunctorBy (WrapHBF t) g => WrapHBF t (WrapF i) g ~> g Source #

appendLB :: forall (f :: Type -> Type). WrapHBF t (ListBy (WrapHBF t) f) (ListBy (WrapHBF t) f) ~> ListBy (WrapHBF t) f Source #

splitNE :: forall (f :: Type -> Type). NonEmptyBy (WrapHBF t) f ~> WrapHBF t f (ListBy (WrapHBF t) f) Source #

splittingLB :: forall (f :: Type -> Type). ListBy (WrapHBF t) f <~> (WrapF i :+: WrapHBF t f (ListBy (WrapHBF t) f)) Source #

toListBy :: forall (f :: Type -> Type). WrapHBF t f f ~> ListBy (WrapHBF t) f Source #

fromNE :: forall (f :: Type -> Type). NonEmptyBy (WrapHBF t) f ~> ListBy (WrapHBF t) f Source #

(Tensor t i, FunctorBy t f, FunctorBy t (WrapLB t f)) => MonoidIn (WrapHBF t) (WrapF i) (WrapLB t f) Source # 
Instance details

Defined in Data.HBifunctor.Tensor

Methods

pureT :: WrapF i ~> WrapLB t f Source #

(Tensor t i, FunctorBy t (Chain t i f)) => MonoidIn (WrapHBF t) (WrapF i) (Chain t i f) Source #

Chain t i is the "free MonoidIn t i". However, we have to wrap t in WrapHBF and i in WrapF to prevent overlapping instances.

Instance details

Defined in Data.HFunctor.Chain

Methods

pureT :: WrapF i ~> Chain t i f Source #

type Rep (WrapF f a) Source # 
Instance details

Defined in Data.HBifunctor.Tensor

type Rep (WrapF f a) = D1 ('MetaData "WrapF" "Data.HBifunctor.Tensor" "functor-combinators-0.3.6.0-inplace" 'True) (C1 ('MetaCons "WrapF" 'PrefixI 'True) (S1 ('MetaSel ('Just "unwrapF") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (f a))))

newtype WrapLB t f a Source #

Any ListBy t f is a SemigroupIn t and a MonoidIn t i, if we have Tensor t i. This newtype wrapper witnesses that fact. We require a newtype wrapper to avoid overlapping instances.

Constructors

WrapLB 

Fields

Instances

Instances details
Functor (ListBy t f) => Functor (WrapLB t f) Source # 
Instance details

Defined in Data.HBifunctor.Tensor

Methods

fmap :: (a -> b) -> WrapLB t f a -> WrapLB t f b #

(<$) :: a -> WrapLB t f b -> WrapLB t f a #

Contravariant (ListBy t f) => Contravariant (WrapLB t f) Source #

Since: 0.3.0.0

Instance details

Defined in Data.HBifunctor.Tensor

Methods

contramap :: (a -> b) -> WrapLB t f b -> WrapLB t f a #

(>$) :: b -> WrapLB t f b -> WrapLB t f a #

Invariant (ListBy t f) => Invariant (WrapLB t f) Source #

Since: 0.3.0.0

Instance details

Defined in Data.HBifunctor.Tensor

Methods

invmap :: (a -> b) -> (b -> a) -> WrapLB t f a -> WrapLB t f b #

(Tensor t i, FunctorBy t f, FunctorBy t (WrapLB t f)) => SemigroupIn (WrapHBF t) (WrapLB t f) Source # 
Instance details

Defined in Data.HBifunctor.Tensor

Methods

biretract :: WrapHBF t (WrapLB t f) (WrapLB t f) ~> WrapLB t f Source #

binterpret :: forall (g :: Type -> Type) (h :: Type -> Type). (g ~> WrapLB t f) -> (h ~> WrapLB t f) -> WrapHBF t g h ~> WrapLB t f Source #

(Tensor t i, FunctorBy t f, FunctorBy t (WrapLB t f)) => MonoidIn (WrapHBF t) (WrapF i) (WrapLB t f) Source # 
Instance details

Defined in Data.HBifunctor.Tensor

Methods

pureT :: WrapF i ~> WrapLB t f Source #

Matchable

class Tensor t i => Matchable t i where Source #

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

Methods

unsplitNE :: FunctorBy t f => t f (ListBy t f) ~> NonEmptyBy t f Source #

The inverse of splitNE. A consing of f to ListBy t f is non-empty, so it can be represented as an NonEmptyBy t f.

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

matchLB :: FunctorBy t f => ListBy t f ~> (i :+: NonEmptyBy t f) Source #

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

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

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

matchLB @Day :: Ap f a -> (Identity :+: Ap1 f) a

Note that you can recursively "unroll" a ListBy completely into a Chain by using unrollLB.

Instances

Instances details
Matchable Day Identity Source # 
Instance details

Defined in Data.HBifunctor.Tensor

Methods

unsplitNE :: forall (f :: Type -> Type). FunctorBy Day f => Day f (ListBy Day f) ~> NonEmptyBy Day f Source #

matchLB :: forall (f :: Type -> Type). FunctorBy Day f => ListBy Day f ~> (Identity :+: NonEmptyBy Day f) Source #

Matchable Day Identity Source # 
Instance details

Defined in Data.HBifunctor.Tensor

Methods

unsplitNE :: forall (f :: Type -> Type). FunctorBy Day f => Day f (ListBy Day f) ~> NonEmptyBy Day f Source #

matchLB :: forall (f :: Type -> Type). FunctorBy Day f => ListBy Day f ~> (Identity :+: NonEmptyBy Day f) Source #

Matchable Night Not Source #

Since: 0.3.0.0

Instance details

Defined in Data.HBifunctor.Tensor

Methods

unsplitNE :: forall (f :: Type -> Type). FunctorBy Night f => Night f (ListBy Night f) ~> NonEmptyBy Night f Source #

matchLB :: forall (f :: Type -> Type). FunctorBy Night f => ListBy Night f ~> (Not :+: NonEmptyBy Night f) Source #

Matchable Night Not Source # 
Instance details

Defined in Data.HBifunctor.Tensor

Methods

unsplitNE :: forall (f :: Type -> Type). FunctorBy Night f => Night f (ListBy Night f) ~> NonEmptyBy Night f Source #

matchLB :: forall (f :: Type -> Type). FunctorBy Night f => ListBy Night f ~> (Not :+: NonEmptyBy Night f) Source #

Matchable Day (Proxy :: Type -> Type) Source #

Instances of Conclude are monoids in the monoidal category on Night.

Since: 0.3.0.0

Instance details

Defined in Data.HBifunctor.Tensor

Methods

unsplitNE :: forall (f :: Type -> Type). FunctorBy Day f => Day f (ListBy Day f) ~> NonEmptyBy Day f Source #

matchLB :: forall (f :: Type -> Type). FunctorBy Day f => ListBy Day f ~> (Proxy :+: NonEmptyBy Day f) Source #

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

Defined in Data.HBifunctor.Tensor

Methods

unsplitNE :: forall (f :: Type -> Type). FunctorBy (:+:) f => (f :+: ListBy (:+:) f) ~> NonEmptyBy (:+:) f Source #

matchLB :: forall (f :: Type -> Type). FunctorBy (:+:) f => ListBy (:+:) f ~> (V1 :+: NonEmptyBy (:+:) f) Source #

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

Defined in Data.HBifunctor.Tensor

Methods

unsplitNE :: forall (f :: Type -> Type). FunctorBy (:*:) f => (f :*: ListBy (:*:) f) ~> NonEmptyBy (:*:) f Source #

matchLB :: forall (f :: Type -> Type). FunctorBy (:*:) f => ListBy (:*:) f ~> (Proxy :+: NonEmptyBy (:*:) f) Source #

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

Defined in Data.HBifunctor.Tensor

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

Defined in Data.HBifunctor.Tensor

Methods

unsplitNE :: forall (f :: Type -> Type). FunctorBy Sum f => Sum f (ListBy Sum f) ~> NonEmptyBy Sum f Source #

matchLB :: forall (f :: Type -> Type). FunctorBy Sum f => ListBy Sum f ~> (V1 :+: NonEmptyBy Sum f) Source #

splittingNE :: (Matchable t i, FunctorBy t f) => NonEmptyBy t f <~> t f (ListBy t f) Source #

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

matchingLB :: forall t i f. (Matchable t i, FunctorBy t f) => ListBy t f <~> (i :+: NonEmptyBy t f) Source #

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

Orphan instances

Tensor Day Identity Source # 
Instance details

Associated Types

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

Methods

intro1 :: forall (f :: Type -> Type). f ~> Day f Identity Source #

intro2 :: forall (g :: Type -> Type). g ~> Day Identity g Source #

elim1 :: forall (f :: Type -> Type). FunctorBy Day f => Day f Identity ~> f Source #

elim2 :: forall (g :: Type -> Type). FunctorBy Day g => Day Identity g ~> g Source #

appendLB :: forall (f :: Type -> Type). Day (ListBy Day f) (ListBy Day f) ~> ListBy Day f Source #

splitNE :: forall (f :: Type -> Type). NonEmptyBy Day f ~> Day f (ListBy Day f) Source #

splittingLB :: forall (f :: Type -> Type). ListBy Day f <~> (Identity :+: Day f (ListBy Day f)) Source #

toListBy :: forall (f :: Type -> Type). Day f f ~> ListBy Day f Source #

fromNE :: forall (f :: Type -> Type). NonEmptyBy Day f ~> ListBy Day f Source #

Tensor Day Identity Source # 
Instance details

Associated Types

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

Methods

intro1 :: forall (f :: Type -> Type). f ~> Day f Identity Source #

intro2 :: forall (g :: Type -> Type). g ~> Day Identity g Source #

elim1 :: forall (f :: Type -> Type). FunctorBy Day f => Day f Identity ~> f Source #

elim2 :: forall (g :: Type -> Type). FunctorBy Day g => Day Identity g ~> g Source #

appendLB :: forall (f :: Type -> Type). Day (ListBy Day f) (ListBy Day f) ~> ListBy Day f Source #

splitNE :: forall (f :: Type -> Type). NonEmptyBy Day f ~> Day f (ListBy Day f) Source #

splittingLB :: forall (f :: Type -> Type). ListBy Day f <~> (Identity :+: Day f (ListBy Day f)) Source #

toListBy :: forall (f :: Type -> Type). Day f f ~> ListBy Day f Source #

fromNE :: forall (f :: Type -> Type). NonEmptyBy Day f ~> ListBy Day f Source #

Tensor Night Not Source #

Since: 0.3.0.0

Instance details

Associated Types

type ListBy Night :: (Type -> Type) -> Type -> Type Source #

Methods

intro1 :: forall (f :: Type -> Type). f ~> Night f Not Source #

intro2 :: forall (g :: Type -> Type). g ~> Night Not g Source #

elim1 :: forall (f :: Type -> Type). FunctorBy Night f => Night f Not ~> f Source #

elim2 :: forall (g :: Type -> Type). FunctorBy Night g => Night Not g ~> g Source #

appendLB :: forall (f :: Type -> Type). Night (ListBy Night f) (ListBy Night f) ~> ListBy Night f Source #

splitNE :: forall (f :: Type -> Type). NonEmptyBy Night f ~> Night f (ListBy Night f) Source #

splittingLB :: forall (f :: Type -> Type). ListBy Night f <~> (Not :+: Night f (ListBy Night f)) Source #

toListBy :: forall (f :: Type -> Type). Night f f ~> ListBy Night f Source #

fromNE :: forall (f :: Type -> Type). NonEmptyBy Night f ~> ListBy Night f Source #

Tensor Night Not Source # 
Instance details

Associated Types

type ListBy Night :: (Type -> Type) -> Type -> Type Source #

Methods

intro1 :: forall (f :: Type -> Type). f ~> Night f Not Source #

intro2 :: forall (g :: Type -> Type). g ~> Night Not g Source #

elim1 :: forall (f :: Type -> Type). FunctorBy Night f => Night f Not ~> f Source #

elim2 :: forall (g :: Type -> Type). FunctorBy Night g => Night Not g ~> g Source #

appendLB :: forall (f :: Type -> Type). Night (ListBy Night f) (ListBy Night f) ~> ListBy Night f Source #

splitNE :: forall (f :: Type -> Type). NonEmptyBy Night f ~> Night f (ListBy Night f) Source #

splittingLB :: forall (f :: Type -> Type). ListBy Night f <~> (Not :+: Night f (ListBy Night f)) Source #

toListBy :: forall (f :: Type -> Type). Night f f ~> ListBy Night f Source #

fromNE :: forall (f :: Type -> Type). NonEmptyBy Night f ~> ListBy Night f Source #

Tensor Day (Proxy :: Type -> Type) Source #

Since: 0.3.0.0

Instance details

Associated Types

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

Methods

intro1 :: forall (f :: Type -> Type). f ~> Day f Proxy Source #

intro2 :: forall (g :: Type -> Type). g ~> Day Proxy g Source #

elim1 :: forall (f :: Type -> Type). FunctorBy Day f => Day f Proxy ~> f Source #

elim2 :: forall (g :: Type -> Type). FunctorBy Day g => Day Proxy g ~> g Source #

appendLB :: forall (f :: Type -> Type). Day (ListBy Day f) (ListBy Day f) ~> ListBy Day f Source #

splitNE :: forall (f :: Type -> Type). NonEmptyBy Day f ~> Day f (ListBy Day f) Source #

splittingLB :: forall (f :: Type -> Type). ListBy Day f <~> (Proxy :+: Day f (ListBy Day f)) Source #

toListBy :: forall (f :: Type -> Type). Day f f ~> ListBy Day f Source #

fromNE :: forall (f :: Type -> Type). NonEmptyBy Day f ~> ListBy Day f Source #

Tensor These1 (V1 :: Type -> Type) Source # 
Instance details

Associated Types

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

Methods

intro1 :: forall (f :: Type -> Type). f ~> These1 f V1 Source #

intro2 :: forall (g :: Type -> Type). g ~> These1 V1 g Source #

elim1 :: forall (f :: Type -> Type). FunctorBy These1 f => These1 f V1 ~> f Source #

elim2 :: forall (g :: Type -> Type). FunctorBy These1 g => These1 V1 g ~> g Source #

appendLB :: forall (f :: Type -> Type). These1 (ListBy These1 f) (ListBy These1 f) ~> ListBy These1 f Source #

splitNE :: forall (f :: Type -> Type). NonEmptyBy These1 f ~> These1 f (ListBy These1 f) Source #

splittingLB :: forall (f :: Type -> Type). ListBy These1 f <~> (V1 :+: These1 f (ListBy These1 f)) Source #

toListBy :: forall (f :: Type -> Type). These1 f f ~> ListBy These1 f Source #

fromNE :: forall (f :: Type -> Type). NonEmptyBy These1 f ~> ListBy These1 f Source #

Tensor (Comp :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Identity Source # 
Instance details

Associated Types

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

Methods

intro1 :: forall (f :: Type -> Type). f ~> Comp f Identity Source #

intro2 :: forall (g :: Type -> Type). g ~> Comp Identity g Source #

elim1 :: forall (f :: Type -> Type). FunctorBy Comp f => Comp f Identity ~> f Source #

elim2 :: forall (g :: Type -> Type). FunctorBy Comp g => Comp Identity g ~> g Source #

appendLB :: forall (f :: Type -> Type). Comp (ListBy Comp f) (ListBy Comp f) ~> ListBy Comp f Source #

splitNE :: forall (f :: Type -> Type). NonEmptyBy Comp f ~> Comp f (ListBy Comp f) Source #

splittingLB :: forall (f :: Type -> Type). ListBy Comp f <~> (Identity :+: Comp f (ListBy Comp f)) Source #

toListBy :: forall (f :: Type -> Type). Comp f f ~> ListBy Comp f Source #

fromNE :: forall (f :: Type -> Type). NonEmptyBy Comp f ~> ListBy Comp f Source #

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

Associated Types

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

Methods

intro1 :: forall (f :: Type -> Type). f ~> (f :+: V1) Source #

intro2 :: forall (g :: Type -> Type). g ~> (V1 :+: g) Source #

elim1 :: forall (f :: Type -> Type). FunctorBy (:+:) f => (f :+: V1) ~> f Source #

elim2 :: forall (g :: Type -> Type). FunctorBy (:+:) g => (V1 :+: g) ~> g Source #

appendLB :: forall (f :: Type -> Type). (ListBy (:+:) f :+: ListBy (:+:) f) ~> ListBy (:+:) f Source #

splitNE :: forall (f :: Type -> Type). NonEmptyBy (:+:) f ~> (f :+: ListBy (:+:) f) Source #

splittingLB :: forall (f :: Type -> Type). ListBy (:+:) f <~> (V1 :+: (f :+: ListBy (:+:) f)) Source #

toListBy :: forall (f :: Type -> Type). (f :+: f) ~> ListBy (:+:) f Source #

fromNE :: forall (f :: Type -> Type). NonEmptyBy (:+:) f ~> ListBy (:+:) f Source #

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

Associated Types

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

Methods

intro1 :: forall (f :: Type -> Type). f ~> (f :*: Proxy) Source #

intro2 :: forall (g :: Type -> Type). g ~> (Proxy :*: g) Source #

elim1 :: forall (f :: Type -> Type). FunctorBy (:*:) f => (f :*: Proxy) ~> f Source #

elim2 :: forall (g :: Type -> Type). FunctorBy (:*:) g => (Proxy :*: g) ~> g Source #

appendLB :: forall (f :: Type -> Type). (ListBy (:*:) f :*: ListBy (:*:) f) ~> ListBy (:*:) f Source #

splitNE :: forall (f :: Type -> Type). NonEmptyBy (:*:) f ~> (f :*: ListBy (:*:) f) Source #

splittingLB :: forall (f :: Type -> Type). ListBy (:*:) f <~> (Proxy :+: (f :*: ListBy (:*:) f)) Source #

toListBy :: forall (f :: Type -> Type). (f :*: f) ~> ListBy (:*:) f Source #

fromNE :: forall (f :: Type -> Type). NonEmptyBy (:*:) f ~> ListBy (:*:) f Source #

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

Associated Types

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

Methods

intro1 :: forall (f :: Type -> Type). f ~> Product f Proxy Source #

intro2 :: forall (g :: Type -> Type). g ~> Product Proxy g Source #

elim1 :: forall (f :: Type -> Type). FunctorBy Product f => Product f Proxy ~> f Source #

elim2 :: forall (g :: Type -> Type). FunctorBy Product g => Product Proxy g ~> g Source #

appendLB :: forall (f :: Type -> Type). Product (ListBy Product f) (ListBy Product f) ~> ListBy Product f Source #

splitNE :: forall (f :: Type -> Type). NonEmptyBy Product f ~> Product f (ListBy Product f) Source #

splittingLB :: forall (f :: Type -> Type). ListBy Product f <~> (Proxy :+: Product f (ListBy Product f)) Source #

toListBy :: forall (f :: Type -> Type). Product f f ~> ListBy Product f Source #

fromNE :: forall (f :: Type -> Type). NonEmptyBy Product f ~> ListBy Product f Source #

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

Associated Types

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

Methods

intro1 :: forall (f :: Type -> Type). f ~> Sum f V1 Source #

intro2 :: forall (g :: Type -> Type). g ~> Sum V1 g Source #

elim1 :: forall (f :: Type -> Type). FunctorBy Sum f => Sum f V1 ~> f Source #

elim2 :: forall (g :: Type -> Type). FunctorBy Sum g => Sum V1 g ~> g Source #

appendLB :: forall (f :: Type -> Type). Sum (ListBy Sum f) (ListBy Sum f) ~> ListBy Sum f Source #

splitNE :: forall (f :: Type -> Type). NonEmptyBy Sum f ~> Sum f (ListBy Sum f) Source #

splittingLB :: forall (f :: Type -> Type). ListBy Sum f <~> (V1 :+: Sum f (ListBy Sum f)) Source #

toListBy :: forall (f :: Type -> Type). Sum f f ~> ListBy Sum f Source #

fromNE :: forall (f :: Type -> Type). NonEmptyBy Sum f ~> ListBy Sum f Source #

Tensor t i => Tensor (WrapHBF t) (WrapF i) Source # 
Instance details

Associated Types

type ListBy (WrapHBF t) :: (Type -> Type) -> Type -> Type Source #

Methods

intro1 :: forall (f :: Type -> Type). f ~> WrapHBF t f (WrapF i) Source #

intro2 :: forall (g :: Type -> Type). g ~> WrapHBF t (WrapF i) g Source #

elim1 :: forall (f :: Type -> Type). FunctorBy (WrapHBF t) f => WrapHBF t f (WrapF i) ~> f Source #

elim2 :: forall (g :: Type -> Type). FunctorBy (WrapHBF t) g => WrapHBF t (WrapF i) g ~> g Source #

appendLB :: forall (f :: Type -> Type). WrapHBF t (ListBy (WrapHBF t) f) (ListBy (WrapHBF t) f) ~> ListBy (WrapHBF t) f Source #

splitNE :: forall (f :: Type -> Type). NonEmptyBy (WrapHBF t) f ~> WrapHBF t f (ListBy (WrapHBF t) f) Source #

splittingLB :: forall (f :: Type -> Type). ListBy (WrapHBF t) f <~> (WrapF i :+: WrapHBF t f (ListBy (WrapHBF t) f)) Source #

toListBy :: forall (f :: Type -> Type). WrapHBF t f f ~> ListBy (WrapHBF t) f Source #

fromNE :: forall (f :: Type -> Type). NonEmptyBy (WrapHBF t) f ~> ListBy (WrapHBF t) f Source #