functor-combinators-0.3.5.1: 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

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 :: SemigroupIn t f => t f f ~> f

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

biretract :: (f :+: f) a -> f a
biretract :: Plus f => (f :*: f) a -> f a
biretract :: Applicative f => Day f f a -> f a
biretract :: Monad f => Comp f f a -> f a

See Data.HBifunctor.Tensor for the next stage of structure in tensors and moving in and out of them.

Synopsis

Associative

class (HBifunctor t, Inject (NonEmptyBy 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.

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

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

Minimal complete definition

associating, appendNE, matchNE

Associated Types

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

The "semigroup functor combinator" generated by t.

A value of type NonEmptyBy 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])     ~ toNonEmptyBy (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 toNonEmptyBy.

See ListBy for a "possibly empty" version of this type.

type FunctorBy t :: (Type -> Type) -> Constraint Source #

A description of "what type of Functor" this tensor is expected to be applied to. This should typically always be either Functor, Contravariant, or Invariant.

Since: 0.3.0.0

Methods

associating :: (FunctorBy t f, FunctorBy t g, FunctorBy t 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.

appendNE :: t (NonEmptyBy t f) (NonEmptyBy t f) ~> NonEmptyBy t f Source #

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

Note that this essentially gives an instance for SemigroupIn t (NonEmptyBy t f), for any functor f.

matchNE :: FunctorBy t f => NonEmptyBy t f ~> (f :+: t f (NonEmptyBy t f)) Source #

If a NonEmptyBy t f represents multiple applications of t f to itself, then we can split it based on whether or not it is just a single f or at least one top-level application of t f.

Note that you can recursively "unroll" a NonEmptyBy completely into a Chain1 by using unrollNE.

consNE :: t f (NonEmptyBy t f) ~> NonEmptyBy t f Source #

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

toNonEmptyBy :: t f f ~> NonEmptyBy t f Source #

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

Instances

Instances details
Associative Day Source # 
Instance details

Defined in Data.HBifunctor.Associative

Associated Types

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

type FunctorBy Day :: (Type -> Type) -> Constraint Source #

Methods

associating :: forall (f :: Type -> Type) (g :: Type -> Type) (h :: Type -> Type). (FunctorBy Day f, FunctorBy Day g, FunctorBy Day h) => Day f (Day g h) <~> Day (Day f g) h Source #

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

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

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

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

Associative Day Source # 
Instance details

Defined in Data.HBifunctor.Associative

Associated Types

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

type FunctorBy Day :: (Type -> Type) -> Constraint Source #

Methods

associating :: forall (f :: Type -> Type) (g :: Type -> Type) (h :: Type -> Type). (FunctorBy Day f, FunctorBy Day g, FunctorBy Day h) => Day f (Day g h) <~> Day (Day f g) h Source #

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

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

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

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

Associative Day Source #

Since: 0.3.0.0

Instance details

Defined in Data.HBifunctor.Associative

Associated Types

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

type FunctorBy Day :: (Type -> Type) -> Constraint Source #

Methods

associating :: forall (f :: Type -> Type) (g :: Type -> Type) (h :: Type -> Type). (FunctorBy Day f, FunctorBy Day g, FunctorBy Day h) => Day f (Day g h) <~> Day (Day f g) h Source #

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

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

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

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

Associative These1 Source #

Ideally here NonEmptyBy would be equivalent to ListBy, 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 NonEmptyBy These1 :: (Type -> Type) -> Type -> Type Source #

type FunctorBy These1 :: (Type -> Type) -> Constraint Source #

Methods

associating :: forall (f :: Type -> Type) (g :: Type -> Type) (h :: Type -> Type). (FunctorBy These1 f, FunctorBy These1 g, FunctorBy These1 h) => These1 f (These1 g h) <~> These1 (These1 f g) h Source #

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

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

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

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

Associative Night Source #

Since: 0.3.0.0

Instance details

Defined in Data.HBifunctor.Associative

Associated Types

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

type FunctorBy Night :: (Type -> Type) -> Constraint Source #

Methods

associating :: forall (f :: Type -> Type) (g :: Type -> Type) (h :: Type -> Type). (FunctorBy Night f, FunctorBy Night g, FunctorBy Night h) => Night f (Night g h) <~> Night (Night f g) h Source #

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

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

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

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

Associative Night Source # 
Instance details

Defined in Data.HBifunctor.Associative

Associated Types

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

type FunctorBy Night :: (Type -> Type) -> Constraint Source #

Methods

associating :: forall (f :: Type -> Type) (g :: Type -> Type) (h :: Type -> Type). (FunctorBy Night f, FunctorBy Night g, FunctorBy Night h) => Night f (Night g h) <~> Night (Night f g) h Source #

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

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

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

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

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

Defined in Data.HBifunctor.Associative

Associated Types

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

type FunctorBy (:+:) :: (Type -> Type) -> Constraint Source #

Methods

associating :: forall (f :: Type -> Type) (g :: Type -> Type) (h :: Type -> Type). (FunctorBy (:+:) f, FunctorBy (:+:) g, FunctorBy (:+:) h) => (f :+: (g :+: h)) <~> ((f :+: g) :+: h) Source #

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

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

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

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

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

Defined in Data.HBifunctor.Associative

Associated Types

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

type FunctorBy (:*:) :: (Type -> Type) -> Constraint Source #

Methods

associating :: forall (f :: Type -> Type) (g :: Type -> Type) (h :: Type -> Type). (FunctorBy (:*:) f, FunctorBy (:*:) g, FunctorBy (:*:) h) => (f :*: (g :*: h)) <~> ((f :*: g) :*: h) Source #

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

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

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

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

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

Defined in Data.HBifunctor.Associative

Associated Types

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

type FunctorBy Product :: (Type -> Type) -> Constraint Source #

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

Defined in Data.HBifunctor.Associative

Associated Types

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

type FunctorBy Sum :: (Type -> Type) -> Constraint Source #

Methods

associating :: forall (f :: Type -> Type) (g :: Type -> Type) (h :: Type -> Type). (FunctorBy Sum f, FunctorBy Sum g, FunctorBy Sum h) => Sum f (Sum g h) <~> Sum (Sum f g) h Source #

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

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

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

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

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

Defined in Data.HBifunctor.Associative

Associated Types

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

type FunctorBy Comp :: (Type -> Type) -> Constraint Source #

Methods

associating :: forall (f :: Type -> Type) (g :: Type -> Type) (h :: Type -> Type). (FunctorBy Comp f, FunctorBy Comp g, FunctorBy Comp h) => Comp f (Comp g h) <~> Comp (Comp f g) h Source #

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

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

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

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

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

Defined in Data.HBifunctor.Associative

Associated Types

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

type FunctorBy Joker :: (Type -> Type) -> Constraint Source #

Methods

associating :: forall (f :: Type -> Type) (g :: Type -> Type) (h :: Type -> Type). (FunctorBy Joker f, FunctorBy Joker g, FunctorBy Joker h) => Joker f (Joker g h) <~> Joker (Joker f g) h Source #

appendNE :: forall (f :: Type -> Type). Joker (NonEmptyBy Joker f) (NonEmptyBy Joker f) ~> NonEmptyBy Joker f Source #

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

consNE :: forall (f :: Type -> Type). Joker f (NonEmptyBy Joker f) ~> NonEmptyBy Joker f Source #

toNonEmptyBy :: forall (f :: Type -> Type). Joker f f ~> NonEmptyBy Joker f Source #

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

Defined in Data.HBifunctor.Associative

Associated Types

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

type FunctorBy LeftF :: (Type -> Type) -> Constraint Source #

Methods

associating :: forall (f :: Type -> Type) (g :: Type -> Type) (h :: Type -> Type). (FunctorBy LeftF f, FunctorBy LeftF g, FunctorBy LeftF h) => LeftF f (LeftF g h) <~> LeftF (LeftF f g) h Source #

appendNE :: forall (f :: Type -> Type). LeftF (NonEmptyBy LeftF f) (NonEmptyBy LeftF f) ~> NonEmptyBy LeftF f Source #

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

consNE :: forall (f :: Type -> Type). LeftF f (NonEmptyBy LeftF f) ~> NonEmptyBy LeftF f Source #

toNonEmptyBy :: forall (f :: Type -> Type). LeftF f f ~> NonEmptyBy LeftF f Source #

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

Defined in Data.HBifunctor.Associative

Associated Types

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

type FunctorBy RightF :: (Type -> Type) -> Constraint Source #

Methods

associating :: forall (f :: Type -> Type) (g :: Type -> Type) (h :: Type -> Type). (FunctorBy RightF f, FunctorBy RightF g, FunctorBy RightF h) => RightF f (RightF g h) <~> RightF (RightF f g) h Source #

appendNE :: forall (f :: Type -> Type). RightF (NonEmptyBy RightF f) (NonEmptyBy RightF f) ~> NonEmptyBy RightF f Source #

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

consNE :: forall (f :: Type -> Type). RightF f (NonEmptyBy RightF f) ~> NonEmptyBy RightF f Source #

toNonEmptyBy :: forall (f :: Type -> Type). RightF f f ~> NonEmptyBy RightF f Source #

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

Defined in Data.HBifunctor.Associative

Associated Types

type NonEmptyBy Void3 :: (Type -> Type) -> Type -> Type Source #

type FunctorBy Void3 :: (Type -> Type) -> Constraint Source #

Methods

associating :: forall (f :: Type -> Type) (g :: Type -> Type) (h :: Type -> Type). (FunctorBy Void3 f, FunctorBy Void3 g, FunctorBy Void3 h) => Void3 f (Void3 g h) <~> Void3 (Void3 f g) h Source #

appendNE :: forall (f :: Type -> Type). Void3 (NonEmptyBy Void3 f) (NonEmptyBy Void3 f) ~> NonEmptyBy Void3 f Source #

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

consNE :: forall (f :: Type -> Type). Void3 f (NonEmptyBy Void3 f) ~> NonEmptyBy Void3 f Source #

toNonEmptyBy :: forall (f :: Type -> Type). Void3 f f ~> NonEmptyBy Void3 f Source #

Associative t => Associative (WrapHBF t) Source # 
Instance details

Defined in Data.HBifunctor.Associative

Associated Types

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

type FunctorBy (WrapHBF t) :: (Type -> Type) -> Constraint Source #

Methods

associating :: forall (f :: Type -> Type) (g :: Type -> Type) (h :: Type -> Type). (FunctorBy (WrapHBF t) f, FunctorBy (WrapHBF t) g, FunctorBy (WrapHBF t) h) => WrapHBF t f (WrapHBF t g h) <~> WrapHBF t (WrapHBF t f g) h Source #

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

matchNE :: forall (f :: Type -> Type). FunctorBy (WrapHBF t) f => NonEmptyBy (WrapHBF t) f ~> (f :+: WrapHBF t f (NonEmptyBy (WrapHBF t) f)) Source #

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

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

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

Reassociate an application of t.

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

Reassociate an application of t.

SemigroupIn

class (Associative t, FunctorBy t f) => SemigroupIn t f where Source #

For different Associative t, we have functors f that we can "squash", using biretract:

t f f ~> f

This gives us the ability to squash applications of t.

Formally, if we have Associative t, we are enriching the category of endofunctors with semigroup structure, turning it into a semigroupoidal category. Different choices of t give different semigroupoidal categories.

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

t f f ~> 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 semigroups in the semigroupoidal category on :+:
  • The class of functors that are semigroups in the semigroupoidal category on :*: is exactly the functors that are instances of Alt.
  • The class of functors that are semigroups in the semigroupoidal category on Day is exactly the functors that are instances of Apply.
  • The class of functors that are semigroups in the semigroupoidal category on Comp is exactly the functors that are instances of Bind.

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

instance Bind f => SemigroupIn Comp 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 newtype wrapper over a type variable, where the second argument also uses a type constructor:

instance SemigroupIn (WrapHBF t) (MyFunctor t i)

This will prevent problems with overloaded instances.

Minimal complete definition

Nothing

Methods

biretract :: t f f ~> f Source #

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

This function makes f a semigroup in the category of endofunctors with respect to tensor t.

default biretract :: Interpret (NonEmptyBy t) f => t f f ~> f Source #

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

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

Note that this is useful in the poly-kinded case, but it is not possible to define generically for all SemigroupIn because it only is defined for Type -> Type inputes. See !+! for a version that is poly-kinded for :+: in specific.

default binterpret :: Interpret (NonEmptyBy t) f => (g ~> f) -> (h ~> f) -> t g h ~> f Source #

Instances

Instances details
Apply f => SemigroupIn Day f Source #

Instances of Apply are semigroups in the semigroupoidal category on Day.

Instance details

Defined in Data.HBifunctor.Associative

Methods

biretract :: Day f f ~> f Source #

binterpret :: forall (g :: Type -> Type) (h :: Type -> Type). (g ~> f) -> (h ~> f) -> Day g h ~> f Source #

Divise f => SemigroupIn Day f Source #

Since: 0.3.0.0

Instance details

Defined in Data.HBifunctor.Associative

Methods

biretract :: Day f f ~> f Source #

binterpret :: forall (g :: Type -> Type) (h :: Type -> Type). (g ~> f) -> (h ~> f) -> Day g h ~> f Source #

Alt f => SemigroupIn These1 f Source # 
Instance details

Defined in Data.HBifunctor.Associative

Methods

biretract :: These1 f f ~> f Source #

binterpret :: forall (g :: Type -> Type) (h :: Type -> Type). (g ~> f) -> (h ~> f) -> These1 g h ~> f Source #

Decide f => SemigroupIn Night f Source #

Since: 0.3.0.0

Instance details

Defined in Data.HBifunctor.Associative

Methods

biretract :: Night f f ~> f Source #

binterpret :: forall (g :: Type -> Type) (h :: Type -> Type). (g ~> f) -> (h ~> f) -> Night g h ~> f Source #

SemigroupIn ((:+:) :: (Type -> Type) -> (Type -> Type) -> Type -> Type) f Source #

All functors are semigroups in the semigroupoidal category on :+:.

Instance details

Defined in Data.HBifunctor.Associative

Methods

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

binterpret :: forall (g :: Type -> Type) (h :: Type -> Type). (g ~> f) -> (h ~> f) -> (g :+: h) ~> f Source #

Alt f => SemigroupIn ((:*:) :: (Type -> Type) -> (Type -> Type) -> Type -> Type) f Source #

Instances of Alt are semigroups in the semigroupoidal category on :*:.

Instance details

Defined in Data.HBifunctor.Associative

Methods

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

binterpret :: forall (g :: Type -> Type) (h :: Type -> Type). (g ~> f) -> (h ~> f) -> (g :*: h) ~> f Source #

Alt f => SemigroupIn (Product :: (Type -> Type) -> (Type -> Type) -> Type -> Type) f Source #

Instances of Alt are semigroups in the semigroupoidal category on Product.

Instance details

Defined in Data.HBifunctor.Associative

Methods

biretract :: Product f f ~> f Source #

binterpret :: forall (g :: Type -> Type) (h :: Type -> Type). (g ~> f) -> (h ~> f) -> Product g h ~> f Source #

SemigroupIn (Sum :: (Type -> Type) -> (Type -> Type) -> Type -> Type) f Source #

All functors are semigroups in the semigroupoidal category on Sum.

Instance details

Defined in Data.HBifunctor.Associative

Methods

biretract :: Sum f f ~> f Source #

binterpret :: forall (g :: Type -> Type) (h :: Type -> Type). (g ~> f) -> (h ~> f) -> Sum g h ~> f Source #

Bind f => SemigroupIn (Comp :: (Type -> Type) -> (Type -> Type) -> Type -> Type) f Source #

Instances of Bind are semigroups in the semigroupoidal category on Comp.

Instance details

Defined in Data.HBifunctor.Associative

Methods

biretract :: Comp f f ~> f Source #

binterpret :: forall (g :: Type -> Type) (h :: Type -> Type). (g ~> f) -> (h ~> f) -> Comp g h ~> f Source #

SemigroupIn (Joker :: (Type -> Type) -> (Type -> Type) -> Type -> Type) f Source # 
Instance details

Defined in Data.HBifunctor.Associative

Methods

biretract :: Joker f f ~> f Source #

binterpret :: forall (g :: Type -> Type) (h :: Type -> Type). (g ~> f) -> (h ~> f) -> Joker g h ~> f Source #

SemigroupIn (LeftF :: (Type -> Type) -> (Type -> Type) -> Type -> Type) f Source # 
Instance details

Defined in Data.HBifunctor.Associative

Methods

biretract :: LeftF f f ~> f Source #

binterpret :: forall (g :: Type -> Type) (h :: Type -> Type). (g ~> f) -> (h ~> f) -> LeftF g h ~> f Source #

SemigroupIn (RightF :: (Type -> Type) -> (Type -> Type) -> Type -> Type) f Source # 
Instance details

Defined in Data.HBifunctor.Associative

Methods

biretract :: RightF f f ~> f Source #

binterpret :: forall (g :: Type -> Type) (h :: Type -> Type). (g ~> f) -> (h ~> f) -> RightF g h ~> f Source #

SemigroupIn (Void3 :: (Type -> Type) -> (Type -> Type) -> Type -> Type) f Source #

All functors are semigroups in the semigroupoidal category on Void3.

Instance details

Defined in Data.HBifunctor.Associative

Methods

biretract :: Void3 f f ~> f Source #

binterpret :: forall (g :: Type -> Type) (h :: Type -> Type). (g ~> f) -> (h ~> f) -> Void3 g h ~> f Source #

(Associative t, FunctorBy t f, FunctorBy t (WrapNE t f)) => SemigroupIn (WrapHBF t) (WrapNE t f) Source # 
Instance details

Defined in Data.HBifunctor.Associative

Methods

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

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

(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 #

(Associative t, FunctorBy t f, FunctorBy t (Chain1 t f)) => SemigroupIn (WrapHBF t) (Chain1 t f) Source #

Chain1 t is the "free SemigroupIn t". However, we have to wrap t in WrapHBF to prevent overlapping instances.

Instance details

Defined in Data.HFunctor.Chain

Methods

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

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

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

We have to wrap t in WrapHBF to prevent overlapping instances.

Instance details

Defined in Data.HFunctor.Chain

Methods

biretract :: WrapHBF t (Chain t i f) (Chain t i f) ~> Chain t i f Source #

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

matchingNE :: (Associative t, FunctorBy t f) => NonEmptyBy t f <~> (f :+: t f (NonEmptyBy t f)) Source #

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

matchingNE states that these two are isomorphic. Use matchNE and inject !*! consNE to convert between one and the other.

retractNE :: forall t f. SemigroupIn t f => NonEmptyBy t f ~> f Source #

An implementation of retract that works for any instance of SemigroupIn t for NonEmptyBy t.

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

interpretNE :: forall t g f. SemigroupIn t f => (g ~> f) -> NonEmptyBy t g ~> f Source #

An implementation of interpret that works for any instance of SemigroupIn t for NonEmptyBy t.

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

Utility

biget :: SemigroupIn t (AltConst 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 g a, if you can convert an f x and g x into b.

Note that depending on the constraints on h in SemigroupIn t h, 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

biapply :: SemigroupIn t (Op b) => (forall x. f x -> x -> b) -> (forall x. g x -> x -> b) -> t f g a -> a -> b Source #

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

Note that depending on the constraints on h in SemigroupIn t h, you may have extra constraints on b.

  • If h is unconstrained, there are no constraints on b
  • If h must be Divise, or Divisible, b needs to be an instance of Semigroup
  • If h must be Divisible, then b needs to be an instance of Monoid.

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

Since: 0.3.2.0

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

Infix alias for binterpret

Note that this is useful in the poly-kinded case, but it is not possible to define generically for all SemigroupIn because it only is defined for Type -> Type inputes. See !+! for a version that is poly-kinded for :+: in specific.

(!$!) :: SemigroupIn t (AltConst 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

(!+!) :: (f ~> h) -> (g ~> h) -> (f :+: g) ~> h infixr 5 Source #

A version of !*! specifically for :+: that is poly-kinded

newtype WrapHBF t f g a Source #

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

Please do not ever define an instance of SemigroupIn "naked" on the second parameter:

instance SemigroupIn (WrapHBF t) f

As that would globally ruin everything using WrapHBF.

Constructors

WrapHBF 

Fields

Instances

Instances details
HBifunctor t => HFunctor (WrapHBF t f :: (k -> Type) -> k -> Type) Source # 
Instance details

Defined in Data.HBifunctor.Associative

Methods

hmap :: forall (f0 :: k0 -> Type) (g :: k0 -> Type). (f0 ~> g) -> WrapHBF t f f0 ~> WrapHBF t f g Source #

HBifunctor t => HBifunctor (WrapHBF t :: (k -> Type) -> (k -> Type) -> k -> Type) Source # 
Instance details

Defined in Data.HBifunctor.Associative

Methods

hleft :: forall (f :: k0 -> Type) (j :: k0 -> Type) (g :: k0 -> Type). (f ~> j) -> WrapHBF t f g ~> WrapHBF t j g Source #

hright :: forall (g :: k0 -> Type) (l :: k0 -> Type) (f :: k0 -> Type). (g ~> l) -> WrapHBF t f g ~> WrapHBF t f l Source #

hbimap :: forall (f :: k0 -> Type) (j :: k0 -> Type) (g :: k0 -> Type) (l :: k0 -> Type). (f ~> j) -> (g ~> l) -> WrapHBF t f g ~> WrapHBF t j l Source #

Associative t => Associative (WrapHBF t) Source # 
Instance details

Defined in Data.HBifunctor.Associative

Associated Types

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

type FunctorBy (WrapHBF t) :: (Type -> Type) -> Constraint Source #

Methods

associating :: forall (f :: Type -> Type) (g :: Type -> Type) (h :: Type -> Type). (FunctorBy (WrapHBF t) f, FunctorBy (WrapHBF t) g, FunctorBy (WrapHBF t) h) => WrapHBF t f (WrapHBF t g h) <~> WrapHBF t (WrapHBF t f g) h Source #

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

matchNE :: forall (f :: Type -> Type). FunctorBy (WrapHBF t) f => NonEmptyBy (WrapHBF t) f ~> (f :+: WrapHBF t f (NonEmptyBy (WrapHBF t) f)) Source #

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

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

(Associative t, FunctorBy t f, FunctorBy t (WrapNE t f)) => SemigroupIn (WrapHBF t) (WrapNE t f) Source # 
Instance details

Defined in Data.HBifunctor.Associative

Methods

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

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

(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 => 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 #

(Associative t, FunctorBy t f, FunctorBy t (Chain1 t f)) => SemigroupIn (WrapHBF t) (Chain1 t f) Source #

Chain1 t is the "free SemigroupIn t". However, we have to wrap t in WrapHBF to prevent overlapping instances.

Instance details

Defined in Data.HFunctor.Chain

Methods

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

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

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

We have to wrap t in WrapHBF to prevent overlapping instances.

Instance details

Defined in Data.HFunctor.Chain

Methods

biretract :: WrapHBF t (Chain t i f) (Chain t i f) ~> Chain t i f Source #

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

Functor (t f g) => Functor (WrapHBF t f g) Source # 
Instance details

Defined in Data.HBifunctor.Associative

Methods

fmap :: (a -> b) -> WrapHBF t f g a -> WrapHBF t f g b #

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

Foldable (t f g) => Foldable (WrapHBF t f g) Source # 
Instance details

Defined in Data.HBifunctor.Associative

Methods

fold :: Monoid m => WrapHBF t f g m -> m #

foldMap :: Monoid m => (a -> m) -> WrapHBF t f g a -> m #

foldMap' :: Monoid m => (a -> m) -> WrapHBF t f g a -> m #

foldr :: (a -> b -> b) -> b -> WrapHBF t f g a -> b #

foldr' :: (a -> b -> b) -> b -> WrapHBF t f g a -> b #

foldl :: (b -> a -> b) -> b -> WrapHBF t f g a -> b #

foldl' :: (b -> a -> b) -> b -> WrapHBF t f g a -> b #

foldr1 :: (a -> a -> a) -> WrapHBF t f g a -> a #

foldl1 :: (a -> a -> a) -> WrapHBF t f g a -> a #

toList :: WrapHBF t f g a -> [a] #

null :: WrapHBF t f g a -> Bool #

length :: WrapHBF t f g a -> Int #

elem :: Eq a => a -> WrapHBF t f g a -> Bool #

maximum :: Ord a => WrapHBF t f g a -> a #

minimum :: Ord a => WrapHBF t f g a -> a #

sum :: Num a => WrapHBF t f g a -> a #

product :: Num a => WrapHBF t f g a -> a #

Traversable (t f g) => Traversable (WrapHBF t f g) Source # 
Instance details

Defined in Data.HBifunctor.Associative

Methods

traverse :: Applicative f0 => (a -> f0 b) -> WrapHBF t f g a -> f0 (WrapHBF t f g b) #

sequenceA :: Applicative f0 => WrapHBF t f g (f0 a) -> f0 (WrapHBF t f g a) #

mapM :: Monad m => (a -> m b) -> WrapHBF t f g a -> m (WrapHBF t f g b) #

sequence :: Monad m => WrapHBF t f g (m a) -> m (WrapHBF t f g a) #

Eq1 (t f g) => Eq1 (WrapHBF t f g) Source # 
Instance details

Defined in Data.HBifunctor.Associative

Methods

liftEq :: (a -> b -> Bool) -> WrapHBF t f g a -> WrapHBF t f g b -> Bool #

Ord1 (t f g) => Ord1 (WrapHBF t f g) Source # 
Instance details

Defined in Data.HBifunctor.Associative

Methods

liftCompare :: (a -> b -> Ordering) -> WrapHBF t f g a -> WrapHBF t f g b -> Ordering #

Show1 (t f g) => Show1 (WrapHBF t f g) Source # 
Instance details

Defined in Data.HBifunctor.Associative

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> WrapHBF t f g a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [WrapHBF t f g a] -> ShowS #

Eq (t f g a) => Eq (WrapHBF t f g a) Source # 
Instance details

Defined in Data.HBifunctor.Associative

Methods

(==) :: WrapHBF t f g a -> WrapHBF t f g a -> Bool #

(/=) :: WrapHBF t f g a -> WrapHBF t f g a -> Bool #

(Typeable f, Typeable g, Typeable a, Typeable t, Typeable k1, Typeable k2, Typeable k3, Data (t f g a)) => Data (WrapHBF t f g a) Source # 
Instance details

Defined in Data.HBifunctor.Associative

Methods

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

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

toConstr :: WrapHBF t f g a -> Constr #

dataTypeOf :: WrapHBF t f g a -> DataType #

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

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

gmapT :: (forall b. Data b => b -> b) -> WrapHBF t f g a -> WrapHBF t f g a #

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

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

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

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

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

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

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

Ord (t f g a) => Ord (WrapHBF t f g a) Source # 
Instance details

Defined in Data.HBifunctor.Associative

Methods

compare :: WrapHBF t f g a -> WrapHBF t f g a -> Ordering #

(<) :: WrapHBF t f g a -> WrapHBF t f g a -> Bool #

(<=) :: WrapHBF t f g a -> WrapHBF t f g a -> Bool #

(>) :: WrapHBF t f g a -> WrapHBF t f g a -> Bool #

(>=) :: WrapHBF t f g a -> WrapHBF t f g a -> Bool #

max :: WrapHBF t f g a -> WrapHBF t f g a -> WrapHBF t f g a #

min :: WrapHBF t f g a -> WrapHBF t f g a -> WrapHBF t f g a #

Read (t f g a) => Read (WrapHBF t f g a) Source # 
Instance details

Defined in Data.HBifunctor.Associative

Methods

readsPrec :: Int -> ReadS (WrapHBF t f g a) #

readList :: ReadS [WrapHBF t f g a] #

readPrec :: ReadPrec (WrapHBF t f g a) #

readListPrec :: ReadPrec [WrapHBF t f g a] #

Show (t f g a) => Show (WrapHBF t f g a) Source # 
Instance details

Defined in Data.HBifunctor.Associative

Methods

showsPrec :: Int -> WrapHBF t f g a -> ShowS #

show :: WrapHBF t f g a -> String #

showList :: [WrapHBF t f g a] -> ShowS #

Generic (WrapHBF t f g a) Source # 
Instance details

Defined in Data.HBifunctor.Associative

Associated Types

type Rep (WrapHBF t f g a) :: Type -> Type #

Methods

from :: WrapHBF t f g a -> Rep (WrapHBF t f g a) x #

to :: Rep (WrapHBF t f g a) x -> WrapHBF t f g a #

type NonEmptyBy (WrapHBF t) Source # 
Instance details

Defined in Data.HBifunctor.Associative

type FunctorBy (WrapHBF t) Source # 
Instance details

Defined in Data.HBifunctor.Associative

type ListBy (WrapHBF t) Source # 
Instance details

Defined in Data.HBifunctor.Tensor

type ListBy (WrapHBF t) = ListBy t
type Rep (WrapHBF t f g a) Source # 
Instance details

Defined in Data.HBifunctor.Associative

type Rep (WrapHBF t f g a) = D1 ('MetaData "WrapHBF" "Data.HBifunctor.Associative" "functor-combinators-0.3.5.1-inplace" 'True) (C1 ('MetaCons "WrapHBF" 'PrefixI 'True) (S1 ('MetaSel ('Just "unwrapHBF") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (t f g a))))

newtype WrapNE t f a Source #

Any NonEmptyBy t f is a SemigroupIn t if we have Associative t. This newtype wrapper witnesses that fact. We require a newtype wrapper to avoid overlapping instances.

Constructors

WrapNE 

Fields

Instances

Instances details
Functor (NonEmptyBy t f) => Functor (WrapNE t f) Source # 
Instance details

Defined in Data.HBifunctor.Associative

Methods

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

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

Contravariant (NonEmptyBy t f) => Contravariant (WrapNE t f) Source # 
Instance details

Defined in Data.HBifunctor.Associative

Methods

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

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

Invariant (NonEmptyBy t f) => Invariant (WrapNE t f) Source # 
Instance details

Defined in Data.HBifunctor.Associative

Methods

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

(Associative t, FunctorBy t f, FunctorBy t (WrapNE t f)) => SemigroupIn (WrapHBF t) (WrapNE t f) Source # 
Instance details

Defined in Data.HBifunctor.Associative

Methods

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

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