generic-functor-0.2.0.0: Deriving generalized functors with GHC.Generics
Safe HaskellNone
LanguageHaskell2010

Generic.Functor.Internal.Implicit

Contents

Synopsis

Documentation

multimapI :: forall arr x y. MultimapI arr x y => arr -> x -> y Source #

Core of multimap

multitraverse :: forall f arr x y. Multitraverse f arr x y => arr -> x -> f y Source #

multifold_ :: forall m arr x y. Multifold_ m arr x y => arr -> Fold m x y Source #

This is kept internal because of the Fold wrapping.

multimapOf :: forall cat arr x y. MultimapOf cat arr x y => arr -> cat x y Source #

class MultimapOf (->) arr x y => MultimapI arr x y Source #

Core of multimap.

Instances

Instances details
MultimapOf ((->) :: Type -> Type -> Type) arr x y => MultimapI arr x y Source # 
Instance details

Defined in Generic.Functor.Internal.Implicit

class MultimapOf (Fold m) arr x y => Multifold_ m arr x y Source #

Constraint for multifold_.

Instances

Instances details
MultimapOf (Fold m) arr x y => Multifold_ m arr x y Source # 
Instance details

Defined in Generic.Functor.Internal.Implicit

class Multitraverse_ f arr x y => Multitraverse f arr x y Source #

Constraint for multitraverse.

Instances

Instances details
Multitraverse_ f arr x y => Multitraverse f arr x y Source # 
Instance details

Defined in Generic.Functor.Internal.Implicit

type Multitraverse_ f arr x y = (MultimapOf (Kleisli f) (WrapKleisli f arr) x y, CoercibleKleisli f (WrapKleisli f arr) arr) Source #

Internal definition of Multitraverse

type family WrapKleisli (f :: Type -> Type) (arr :: Type) Source #

Instances

Instances details
type WrapKleisli _f NilArr Source # 
Instance details

Defined in Generic.Functor.Internal.Implicit

type WrapKleisli f (a -> f b) Source # 
Instance details

Defined in Generic.Functor.Internal.Implicit

type WrapKleisli f (a -> f b) = Kleisli f a b
type WrapKleisli f (a :+ arr) Source # 
Instance details

Defined in Generic.Functor.Internal.Implicit

type WrapKleisli f (a :+ arr) = WrapKleisli f a :+ WrapKleisli f arr
type WrapKleisli _f (Rule rule mode) Source # 
Instance details

Defined in Generic.Functor.Internal.Implicit

type WrapKleisli _f (Rule rule mode) = Rule rule mode

class Coercible warr arr => CoercibleKleisli (f :: Type -> Type) warr arr Source #

Auxiliary constraint for Multitraverse

Instances

Instances details
d ~ NilArr => CoercibleKleisli f d NilArr Source # 
Instance details

Defined in Generic.Functor.Internal.Implicit

(b2 ~ f c, a ~ Kleisli f b1 c) => CoercibleKleisli f a (b1 -> b2) Source # 
Instance details

Defined in Generic.Functor.Internal.Implicit

d ~ Rule rule mode => CoercibleKleisli f d (Rule rule mode) Source # 
Instance details

Defined in Generic.Functor.Internal.Implicit

(CoercibleKleisli f a b, CoercibleKleisli f arr arr') => CoercibleKleisli f (a :+ arr) (b :+ arr') Source # 
Instance details

Defined in Generic.Functor.Internal.Implicit

class Multimap_ cat (S2 arr) x y => MultimapOf cat arr x y Source #

Instances

Instances details
Multimap_ cat (S2 arr) x y => MultimapOf cat arr x y Source # 
Instance details

Defined in Generic.Functor.Internal.Implicit

newtype Fold m x y Source #

Fold m is like Kleisli (Const m), but it has a different FunctorOf instance, with Foldable instead of Traversable.

Constructors

Fold 

Fields

Instances

Instances details
Monoid m => CatLike (Fold m) Source # 
Instance details

Defined in Generic.Functor.Internal.Implicit

Methods

catid :: Fold m x x Source #

(Bifoldable t, Monoid m) => BifunctorOf (Fold m) t Source # 
Instance details

Defined in Generic.Functor.Internal.Implicit

Methods

catbimap :: Fold m a b -> Fold m c d -> Fold m (t a c) (t b d) Source #

(Foldable t, Monoid m) => FunctorOf (Fold m) t Source # 
Instance details

Defined in Generic.Functor.Internal.Implicit

Methods

catmap :: Fold m a b -> Fold m (t a) (t b) Source #

Internal

class CatLike cat where Source #

Methods

catid :: cat x x Source #

Instances

Instances details
Applicative f => CatLike (Kleisli f) Source # 
Instance details

Defined in Generic.Functor.Internal.Implicit

Methods

catid :: Kleisli f x x Source #

Monoid m => CatLike (Fold m) Source # 
Instance details

Defined in Generic.Functor.Internal.Implicit

Methods

catid :: Fold m x x Source #

CatLike ((->) :: Type -> Type -> Type) Source # 
Instance details

Defined in Generic.Functor.Internal.Implicit

Methods

catid :: x -> x Source #

class FunctorOf cat t where Source #

Methods

catmap :: cat a b -> cat (t a) (t b) Source #

Instances

Instances details
(Applicative f, Traversable t) => FunctorOf (Kleisli f) t Source # 
Instance details

Defined in Generic.Functor.Internal.Implicit

Methods

catmap :: Kleisli f a b -> Kleisli f (t a) (t b) Source #

(Foldable t, Monoid m) => FunctorOf (Fold m) t Source # 
Instance details

Defined in Generic.Functor.Internal.Implicit

Methods

catmap :: Fold m a b -> Fold m (t a) (t b) Source #

Functor t => FunctorOf ((->) :: Type -> Type -> Type) t Source # 
Instance details

Defined in Generic.Functor.Internal.Implicit

Methods

catmap :: (a -> b) -> t a -> t b Source #

class BifunctorOf cat t where Source #

Methods

catbimap :: cat a b -> cat c d -> cat (t a c) (t b d) Source #

Instances

Instances details
(Applicative f, Bitraversable t) => BifunctorOf (Kleisli f) t Source # 
Instance details

Defined in Generic.Functor.Internal.Implicit

Methods

catbimap :: Kleisli f a b -> Kleisli f c d -> Kleisli f (t a c) (t b d) Source #

(Bifoldable t, Monoid m) => BifunctorOf (Fold m) t Source # 
Instance details

Defined in Generic.Functor.Internal.Implicit

Methods

catbimap :: Fold m a b -> Fold m c d -> Fold m (t a c) (t b d) Source #

Bifunctor t => BifunctorOf ((->) :: Type -> Type -> Type) t Source # 
Instance details

Defined in Generic.Functor.Internal.Implicit

Methods

catbimap :: (a -> b) -> (c -> d) -> t a c -> t b d Source #

class Multimap_ cat arr x y where Source #

Internal implementation of MultimapOf.

Methods

multimap_ :: arr -> cat x y Source #

Instances

Instances details
CatLike cat => Multimap_ cat (S arr (Rule AnyId Incoherent :+ arr')) x x Source # 
Instance details

Defined in Generic.Functor.Internal.Implicit

Methods

multimap_ :: S arr (Rule AnyId Incoherent :+ arr') -> cat x x Source #

Multimap_ cat (S arr (cat a b :+ arr')) a b Source # 
Instance details

Defined in Generic.Functor.Internal.Implicit

Methods

multimap_ :: S arr (cat a b :+ arr') -> cat a b Source #

Multimap_ cat (S arr arr') x y => Multimap_ cat (S arr (() :+ arr')) x y Source # 
Instance details

Defined in Generic.Functor.Internal.Implicit

Methods

multimap_ :: S arr (() :+ arr') -> cat x y Source #

Multimap_ cat (S arr arr') x y => Multimap_ cat (S arr (NilArr :+ arr')) x y Source # 
Instance details

Defined in Generic.Functor.Internal.Implicit

Methods

multimap_ :: S arr (NilArr :+ arr') -> cat x y Source #

Multimap_ cat (S arr (arr0 :+ (arr1 :+ arr2))) x y => Multimap_ cat (S arr ((arr0 :+ arr1) :+ arr2)) x y Source # 
Instance details

Defined in Generic.Functor.Internal.Implicit

Methods

multimap_ :: S arr ((arr0 :+ arr1) :+ arr2) -> cat x y Source #

Multimap_ cat (S arr arr') x y => Multimap_ cat (S arr (arr0 :+ arr')) x y Source # 
Instance details

Defined in Generic.Functor.Internal.Implicit

Methods

multimap_ :: S arr (arr0 :+ arr') -> cat x y Source #

(FunctorOf cat f, MultimapOf cat arr x y) => Multimap_ cat (S arr (Rule AnyFunctor Incoherent :+ arr')) (f x) (f y) Source # 
Instance details

Defined in Generic.Functor.Internal.Implicit

Methods

multimap_ :: S arr (Rule AnyFunctor Incoherent :+ arr') -> cat (f x) (f y) Source #

(BifunctorOf cat f, MultimapOf cat arr x1 y1, MultimapOf cat arr x2 y2) => Multimap_ cat (S arr (Rule AnyBifunctor Incoherent :+ arr')) (f x1 x2) (f y1 y2) Source # 
Instance details

Defined in Generic.Functor.Internal.Implicit

Methods

multimap_ :: S arr (Rule AnyBifunctor Incoherent :+ arr') -> cat (f x1 x2) (f y1 y2) Source #

(MultimapOf ((->) :: Type -> Type -> Type) arr y1 x1, MultimapOf ((->) :: Type -> Type -> Type) arr x2 y2) => Multimap_ ((->) :: Type -> Type -> Type) (S arr (Rule AnyBifunctor Incoherent :+ arr')) (x1 -> x2) (y1 -> y2) Source # 
Instance details

Defined in Generic.Functor.Internal.Implicit

Methods

multimap_ :: S arr (Rule AnyBifunctor Incoherent :+ arr') -> (x1 -> x2) -> (y1 -> y2) Source #

data a :+ b infixr 1 Source #

Heterogeneous lists of arrows are constructed as lists separated by (:+) and terminated by ().

Example

Given f :: a -> a' and g :: b -> b', (f :+ g :+ ()) is a list with the two elements f and g.

if
  f :: a -> a'
  g :: b -> b'

then
  f :+ g :+ ()  ::  (a -> a') :+ (b -> b') :+ ()

Those lists are used by gmultimap and multimap.

bimap_ :: (a -> a') -> (b -> b') -> (Maybe a, [Either b a]) -> (Maybe a', [Either b' a'])
bimap_ f g = multimap (f :+ g :+ ())

Constructors

a :+ b infixr 1 

Instances

Instances details
CatLike cat => Multimap_ cat (S arr (Rule AnyId Incoherent :+ arr')) x x Source # 
Instance details

Defined in Generic.Functor.Internal.Implicit

Methods

multimap_ :: S arr (Rule AnyId Incoherent :+ arr') -> cat x x Source #

Multimap_ cat (S arr (cat a b :+ arr')) a b Source # 
Instance details

Defined in Generic.Functor.Internal.Implicit

Methods

multimap_ :: S arr (cat a b :+ arr') -> cat a b Source #

Multimap_ cat (S arr arr') x y => Multimap_ cat (S arr (() :+ arr')) x y Source # 
Instance details

Defined in Generic.Functor.Internal.Implicit

Methods

multimap_ :: S arr (() :+ arr') -> cat x y Source #

Multimap_ cat (S arr arr') x y => Multimap_ cat (S arr (NilArr :+ arr')) x y Source # 
Instance details

Defined in Generic.Functor.Internal.Implicit

Methods

multimap_ :: S arr (NilArr :+ arr') -> cat x y Source #

Multimap_ cat (S arr (arr0 :+ (arr1 :+ arr2))) x y => Multimap_ cat (S arr ((arr0 :+ arr1) :+ arr2)) x y Source # 
Instance details

Defined in Generic.Functor.Internal.Implicit

Methods

multimap_ :: S arr ((arr0 :+ arr1) :+ arr2) -> cat x y Source #

Multimap_ cat (S arr arr') x y => Multimap_ cat (S arr (arr0 :+ arr')) x y Source # 
Instance details

Defined in Generic.Functor.Internal.Implicit

Methods

multimap_ :: S arr (arr0 :+ arr') -> cat x y Source #

(FunctorOf cat f, MultimapOf cat arr x y) => Multimap_ cat (S arr (Rule AnyFunctor Incoherent :+ arr')) (f x) (f y) Source # 
Instance details

Defined in Generic.Functor.Internal.Implicit

Methods

multimap_ :: S arr (Rule AnyFunctor Incoherent :+ arr') -> cat (f x) (f y) Source #

(CoercibleKleisli f a b, CoercibleKleisli f arr arr') => CoercibleKleisli f (a :+ arr) (b :+ arr') Source # 
Instance details

Defined in Generic.Functor.Internal.Implicit

(BifunctorOf cat f, MultimapOf cat arr x1 y1, MultimapOf cat arr x2 y2) => Multimap_ cat (S arr (Rule AnyBifunctor Incoherent :+ arr')) (f x1 x2) (f y1 y2) Source # 
Instance details

Defined in Generic.Functor.Internal.Implicit

Methods

multimap_ :: S arr (Rule AnyBifunctor Incoherent :+ arr') -> cat (f x1 x2) (f y1 y2) Source #

(MultimapOf ((->) :: Type -> Type -> Type) arr y1 x1, MultimapOf ((->) :: Type -> Type -> Type) arr x2 y2) => Multimap_ ((->) :: Type -> Type -> Type) (S arr (Rule AnyBifunctor Incoherent :+ arr')) (x1 -> x2) (y1 -> y2) Source # 
Instance details

Defined in Generic.Functor.Internal.Implicit

Methods

multimap_ :: S arr (Rule AnyBifunctor Incoherent :+ arr') -> (x1 -> x2) -> (y1 -> y2) Source #

type WrapKleisli f (a :+ arr) Source # 
Instance details

Defined in Generic.Functor.Internal.Implicit

type WrapKleisli f (a :+ arr) = WrapKleisli f a :+ WrapKleisli f arr

data Rule rule mode Source #

Constructors

Rule rule mode 

Instances

Instances details
d ~ Rule rule mode => CoercibleKleisli f d (Rule rule mode) Source # 
Instance details

Defined in Generic.Functor.Internal.Implicit

CatLike cat => Multimap_ cat (S arr (Rule AnyId Incoherent :+ arr')) x x Source # 
Instance details

Defined in Generic.Functor.Internal.Implicit

Methods

multimap_ :: S arr (Rule AnyId Incoherent :+ arr') -> cat x x Source #

(FunctorOf cat f, MultimapOf cat arr x y) => Multimap_ cat (S arr (Rule AnyFunctor Incoherent :+ arr')) (f x) (f y) Source # 
Instance details

Defined in Generic.Functor.Internal.Implicit

Methods

multimap_ :: S arr (Rule AnyFunctor Incoherent :+ arr') -> cat (f x) (f y) Source #

(BifunctorOf cat f, MultimapOf cat arr x1 y1, MultimapOf cat arr x2 y2) => Multimap_ cat (S arr (Rule AnyBifunctor Incoherent :+ arr')) (f x1 x2) (f y1 y2) Source # 
Instance details

Defined in Generic.Functor.Internal.Implicit

Methods

multimap_ :: S arr (Rule AnyBifunctor Incoherent :+ arr') -> cat (f x1 x2) (f y1 y2) Source #

(MultimapOf ((->) :: Type -> Type -> Type) arr y1 x1, MultimapOf ((->) :: Type -> Type -> Type) arr x2 y2) => Multimap_ ((->) :: Type -> Type -> Type) (S arr (Rule AnyBifunctor Incoherent :+ arr')) (x1 -> x2) (y1 -> y2) Source # 
Instance details

Defined in Generic.Functor.Internal.Implicit

Methods

multimap_ :: S arr (Rule AnyBifunctor Incoherent :+ arr') -> (x1 -> x2) -> (y1 -> y2) Source #

type WrapKleisli _f (Rule rule mode) Source # 
Instance details

Defined in Generic.Functor.Internal.Implicit

type WrapKleisli _f (Rule rule mode) = Rule rule mode

data AnyId Source #

Constructors

AnyId 

Instances

Instances details
CatLike cat => Multimap_ cat (S arr (Rule AnyId Incoherent :+ arr')) x x Source # 
Instance details

Defined in Generic.Functor.Internal.Implicit

Methods

multimap_ :: S arr (Rule AnyId Incoherent :+ arr') -> cat x x Source #

data AnyFunctor Source #

Constructors

AnyFunctor 

Instances

Instances details
(FunctorOf cat f, MultimapOf cat arr x y) => Multimap_ cat (S arr (Rule AnyFunctor Incoherent :+ arr')) (f x) (f y) Source # 
Instance details

Defined in Generic.Functor.Internal.Implicit

Methods

multimap_ :: S arr (Rule AnyFunctor Incoherent :+ arr') -> cat (f x) (f y) Source #

data AnyBifunctor Source #

Constructors

AnyBifunctor 

Instances

Instances details
(BifunctorOf cat f, MultimapOf cat arr x1 y1, MultimapOf cat arr x2 y2) => Multimap_ cat (S arr (Rule AnyBifunctor Incoherent :+ arr')) (f x1 x2) (f y1 y2) Source # 
Instance details

Defined in Generic.Functor.Internal.Implicit

Methods

multimap_ :: S arr (Rule AnyBifunctor Incoherent :+ arr') -> cat (f x1 x2) (f y1 y2) Source #

(MultimapOf ((->) :: Type -> Type -> Type) arr y1 x1, MultimapOf ((->) :: Type -> Type -> Type) arr x2 y2) => Multimap_ ((->) :: Type -> Type -> Type) (S arr (Rule AnyBifunctor Incoherent :+ arr')) (x1 -> x2) (y1 -> y2) Source # 
Instance details

Defined in Generic.Functor.Internal.Implicit

Methods

multimap_ :: S arr (Rule AnyBifunctor Incoherent :+ arr') -> (x1 -> x2) -> (y1 -> y2) Source #

data NilArr Source #

Constructors

NilArr 

Instances

Instances details
d ~ NilArr => CoercibleKleisli f d NilArr Source # 
Instance details

Defined in Generic.Functor.Internal.Implicit

Multimap_ cat (S arr arr') x y => Multimap_ cat (S arr (NilArr :+ arr')) x y Source # 
Instance details

Defined in Generic.Functor.Internal.Implicit

Methods

multimap_ :: S arr (NilArr :+ arr') -> cat x y Source #

type WrapKleisli _f NilArr Source # 
Instance details

Defined in Generic.Functor.Internal.Implicit

data Incoherent Source #

Constructors

Incoherent 

Instances

Instances details
CatLike cat => Multimap_ cat (S arr (Rule AnyId Incoherent :+ arr')) x x Source # 
Instance details

Defined in Generic.Functor.Internal.Implicit

Methods

multimap_ :: S arr (Rule AnyId Incoherent :+ arr') -> cat x x Source #

(FunctorOf cat f, MultimapOf cat arr x y) => Multimap_ cat (S arr (Rule AnyFunctor Incoherent :+ arr')) (f x) (f y) Source # 
Instance details

Defined in Generic.Functor.Internal.Implicit

Methods

multimap_ :: S arr (Rule AnyFunctor Incoherent :+ arr') -> cat (f x) (f y) Source #

(BifunctorOf cat f, MultimapOf cat arr x1 y1, MultimapOf cat arr x2 y2) => Multimap_ cat (S arr (Rule AnyBifunctor Incoherent :+ arr')) (f x1 x2) (f y1 y2) Source # 
Instance details

Defined in Generic.Functor.Internal.Implicit

Methods

multimap_ :: S arr (Rule AnyBifunctor Incoherent :+ arr') -> cat (f x1 x2) (f y1 y2) Source #

(MultimapOf ((->) :: Type -> Type -> Type) arr y1 x1, MultimapOf ((->) :: Type -> Type -> Type) arr x2 y2) => Multimap_ ((->) :: Type -> Type -> Type) (S arr (Rule AnyBifunctor Incoherent :+ arr')) (x1 -> x2) (y1 -> y2) Source # 
Instance details

Defined in Generic.Functor.Internal.Implicit

Methods

multimap_ :: S arr (Rule AnyBifunctor Incoherent :+ arr') -> (x1 -> x2) -> (y1 -> y2) Source #

type Default mode arr = arr :+ (Rule AnyId mode :+ (Rule AnyFunctor mode :+ (Rule AnyBifunctor mode :+ NilArr))) Source #

def :: mode -> arr -> Default mode arr Source #

data S arr arr' Source #

arr is the list of arrows provided by the user. It is constant. When testing whether any arrow matches, arr' is the remaining list of arrows to be tested.

Constructors

S arr arr' 

Instances

Instances details
CatLike cat => Multimap_ cat (S arr (Rule AnyId Incoherent :+ arr')) x x Source # 
Instance details

Defined in Generic.Functor.Internal.Implicit

Methods

multimap_ :: S arr (Rule AnyId Incoherent :+ arr') -> cat x x Source #

Multimap_ cat (S arr (cat a b :+ arr')) a b Source # 
Instance details

Defined in Generic.Functor.Internal.Implicit

Methods

multimap_ :: S arr (cat a b :+ arr') -> cat a b Source #

Multimap_ cat (S arr arr') x y => Multimap_ cat (S arr (() :+ arr')) x y Source # 
Instance details

Defined in Generic.Functor.Internal.Implicit

Methods

multimap_ :: S arr (() :+ arr') -> cat x y Source #

Multimap_ cat (S arr arr') x y => Multimap_ cat (S arr (NilArr :+ arr')) x y Source # 
Instance details

Defined in Generic.Functor.Internal.Implicit

Methods

multimap_ :: S arr (NilArr :+ arr') -> cat x y Source #

Multimap_ cat (S arr (arr0 :+ (arr1 :+ arr2))) x y => Multimap_ cat (S arr ((arr0 :+ arr1) :+ arr2)) x y Source # 
Instance details

Defined in Generic.Functor.Internal.Implicit

Methods

multimap_ :: S arr ((arr0 :+ arr1) :+ arr2) -> cat x y Source #

Multimap_ cat (S arr arr') x y => Multimap_ cat (S arr (arr0 :+ arr')) x y Source # 
Instance details

Defined in Generic.Functor.Internal.Implicit

Methods

multimap_ :: S arr (arr0 :+ arr') -> cat x y Source #

(FunctorOf cat f, MultimapOf cat arr x y) => Multimap_ cat (S arr (Rule AnyFunctor Incoherent :+ arr')) (f x) (f y) Source # 
Instance details

Defined in Generic.Functor.Internal.Implicit

Methods

multimap_ :: S arr (Rule AnyFunctor Incoherent :+ arr') -> cat (f x) (f y) Source #

(BifunctorOf cat f, MultimapOf cat arr x1 y1, MultimapOf cat arr x2 y2) => Multimap_ cat (S arr (Rule AnyBifunctor Incoherent :+ arr')) (f x1 x2) (f y1 y2) Source # 
Instance details

Defined in Generic.Functor.Internal.Implicit

Methods

multimap_ :: S arr (Rule AnyBifunctor Incoherent :+ arr') -> cat (f x1 x2) (f y1 y2) Source #

(MultimapOf ((->) :: Type -> Type -> Type) arr y1 x1, MultimapOf ((->) :: Type -> Type -> Type) arr x2 y2) => Multimap_ ((->) :: Type -> Type -> Type) (S arr (Rule AnyBifunctor Incoherent :+ arr')) (x1 -> x2) (y1 -> y2) Source # 
Instance details

Defined in Generic.Functor.Internal.Implicit

Methods

multimap_ :: S arr (Rule AnyBifunctor Incoherent :+ arr') -> (x1 -> x2) -> (y1 -> y2) Source #

type S2 arr = S arr arr Source #

s2 :: arr -> S2 arr Source #