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

Generic.Functor.Internal

Description

This is an internal module. Look, don't touch.

Generic.Functor is the public API.

Synopsis

Documentation

gfmap :: forall f a b. GFunctor f => (a -> b) -> f a -> f b Source #

Generic implementation of fmap. See also GenericFunctor for DerivingVia, using gfmap under the hood.

Example

{-# LANGUAGE DeriveGeneric #-}

import GHC.Generics (Generic)
import Generic.Functor (gfmap)

data Twice a = Twice (Either a a)
  deriving Generic

instance Functor Twice where
  fmap = gfmap

Unlike gsolomap, gfmap is safe to use in all contexts.

gsolomap :: forall a b x y. (Generic x, Generic y, GSolomap a b x y) => (a -> b) -> x -> y Source #

Generalized generic functor.

gsolomap is a generalization of gfmap (generic fmap), where the type parameter to be "mapped" does not have to be the last one.

gsolomap is unsafe: misuse will break your programs. Read the Usage section below for details.

Example

{-# LANGUAGE DeriveGeneric #-}

import GHC.Generics (Generic)
import Generic.Functor (gsolomap)

data Result a r = Error a | Ok r  -- Another name for Either
  deriving Generic

mapError :: (a -> b) -> Result a r -> Result b r
mapError = gsolomap

mapOk :: (r -> s) -> Result a r -> Result a s
mapOk = gsolomap

mapBoth :: (a -> b) -> Result a a -> Result b b
mapBoth = gsolomap

Usage

(This also applies to solomap, gmultimap, and multimap.)

gsolomap should only be used to define polymorphic "fmap-like functions". It works only in contexts where a and b are two distinct, non-unifiable type variables. This is usually the case when they are bound by universal quantification (forall a b. ...), with no equality constraints on a and b.

The one guarantee of gsolomap is that gsolomap id = id. Under the above conditions, that law and the types should uniquely determine the implementation, which gsolomap seeks automatically.

The unsafety is due to the use of incoherent instances as part of the definition of GSolomap. Functions are safe to specialize after GSolomap (and Solomap) constraints have been discharged.

Note also that the type parameters of gsolomap must all be determined by the context. For instance, composing two gsolomap, as in gsolomap f . gsolomap g, is a type error because the type in the middle cannot be inferred.

solomap :: forall a b x y. Solomap a b x y => (a -> b) -> x -> y Source #

Generalized implicit functor.

Use this when x and y are applications of existing functors (Functor, Bifunctor).

This is a different use case from gfmap and gsolomap, which make functors out of freshly declared data types.

solomap is unsafe: misuse will break your programs.

See the Usage section of gsolomap for details.

Example

map1 :: (a -> b) -> Either e (Maybe [IO a]) -> Either e (Maybe [IO b])
map1 = solomap
-- equivalent to:   fmap . fmap . fmap . fmap

map2 :: (a -> b) -> (e -> Either [a] r) -> (e -> Either [b] r)
map2 = solomap
-- equivalent to:   \f -> fmap (bimap (fmap f) id)

gmultimap :: forall arr x y. (Generic x, Generic y, GMultimap arr x y) => arr -> x -> y Source #

Generic n-ary functor.

A generalization of gsolomap to map over multiple parameters simultaneously. gmultimap takes a list of functions separated by (:+) and terminated by ().

gmultimap is unsafe: misuse will break your programs. The type of every function in the list must be some (a -> b) where a and b are distinct type variables.

See the Usage section of gsolomap for details.

Example

{-# LANGUAGE DeriveGeneric #-}

import GHC.Generics (Generic)
import Generic.Functor (gmultimap)

data Three a b c = One a | Two b | Three c
  deriving Generic

mapThree :: (a -> a') -> (b -> b') -> (c -> c') -> Three a b c -> Three a' b' c'
mapThree f g h = gmultimap (f :+ g :+ h :+ ())

multimap :: forall arr x y. Multimap arr x y => arr -> x -> y Source #

Implicit n-ary functor.

A generalization of solomap to map over multiple parameters simultaneously. multimap takes a list of functions separated by (:+) and terminated by ().

multimap is unsafe: misuse will break your programs. The type of every function in the list must be some (a -> b) where a and b are distinct type variables.

See the Usage section of gsolomap for details.

Example

type F a b c = Either a (b, c)

map3 :: (a -> a') -> (b -> b') -> (c -> c') -> F a b c -> F a' b' c'
map3 f g h = multimap (f :+ g :+ h :+ ())
-- equivalent to:  \f g h -> bimap f (bimap g h)

gbimap :: forall f a b c d. GBimap f => (a -> b) -> (c -> d) -> f a c -> f b d Source #

Generic implementation of bimap from Bifunctor. See also GenericBifunctor.

gfirst :: forall f a b c. GFirst f => (a -> b) -> f a c -> f b c Source #

Generic implementation of first from Bifunctor. See also GenericBifunctor.

gsecond :: forall f a c d. GSecond f => (c -> d) -> f a c -> f a d Source #

Generic implementation of second from Bifunctor. See also GenericBifunctor.

Fold

gfoldMap :: forall t m a. (GFoldMap m t, Monoid m) => (a -> m) -> t a -> m Source #

Generic implementation of foldMap from Foldable.

gbifoldMap :: forall t m a b. (GBifoldMap m t, Monoid m) => (a -> m) -> (b -> m) -> t a b -> m Source #

Generic implementation of bifoldMap from Bifoldable.

Traverse

gtraverse :: forall t f a b. (GTraverse f t, Applicative f) => (a -> f b) -> t a -> f (t b) Source #

Generic implementation of traverse from Traversable.

gbitraverse :: forall t f a b c d. (GBitraverse f t, Applicative f) => (a -> f b) -> (c -> f d) -> t a c -> f (t b d) Source #

Generic implementation of bitraverse from Bitraversable.

with :: forall c r. (c => r) -> c => r Source #

Explicitly require a constraint, to force the instantiation of a quantified constraint.

Top-level constraints

gfmap

class (forall a. Generic (f a), forall a b. GFunctorRep a b f) => GFunctor f Source #

Generic Functor. Constraint for gfmap.

Instances

Instances details
(forall a. Generic (f a), forall a b. GFunctorRep a b f) => GFunctor f Source # 
Instance details

Defined in Generic.Functor.Internal

class GMap1 (Default Incoherent (a -> b)) (Rep (f a)) (Rep (f b)) => GFunctorRep a b f Source #

Internal component of GFunctor.

This is an example of the "quantified constraints trick" to encode forall a b. GMap1 a b (Rep (f a)) (Rep (f b)) which doesn't actually work as-is.

Instances

Instances details
GMap1 (Default Incoherent (a -> b)) (Rep (f a)) (Rep (f b)) => GFunctorRep a b f Source # 
Instance details

Defined in Generic.Functor.Internal

gbimap

class (forall a c. Generic (f a c), forall a b c d. GBimapRep a b c d f) => GBimap f Source #

Constraint for gbimap.

Instances

Instances details
(forall a c. Generic (f a c), forall a b c d. GBimapRep a b c d f) => GBimap f Source # 
Instance details

Defined in Generic.Functor.Internal

class GMap1 (Default Incoherent ((a -> b) :+ (c -> d))) (Rep (f a c)) (Rep (f b d)) => GBimapRep a b c d f Source #

Internal component of GBifunctor.

Instances

Instances details
GMap1 (Default Incoherent ((a -> b) :+ (c -> d))) (Rep (f a c)) (Rep (f b d)) => GBimapRep a b c d f Source # 
Instance details

Defined in Generic.Functor.Internal

gfirst

class (forall a c. Generic (f a c), forall a b c. GFirstRep a b c f) => GFirst f Source #

Constraint for gfirst.

Instances

Instances details
(forall a c. Generic (f a c), forall a b c. GFirstRep a b c f) => GFirst f Source # 
Instance details

Defined in Generic.Functor.Internal

class GMap1 (Default Incoherent (a -> b)) (Rep (f a c)) (Rep (f b c)) => GFirstRep a b c f Source #

Internal component of GFirst.

Instances

Instances details
GMap1 (Default Incoherent (a -> b)) (Rep (f a c)) (Rep (f b c)) => GFirstRep a b c f Source # 
Instance details

Defined in Generic.Functor.Internal

gsecond

class (forall a c. Generic (f a c), forall a c d. GFunctorRep c d (f a)) => GSecond f Source #

Constraint for gsecond.

Instances

Instances details
(forall a c. Generic (f a c), forall a c d. GFunctorRep c d (f a)) => GSecond f Source # 
Instance details

Defined in Generic.Functor.Internal

class (GBimap f, GFirst f, GSecond f) => GBifunctor f Source #

Generic Bifunctor.

Instances

Instances details
(GBimap f, GFirst f, GSecond f) => GBifunctor f Source # 
Instance details

Defined in Generic.Functor.Internal

gtraverse

class (forall a. Generic (t a), forall a b. GTraverseRep a b f t) => GTraverse f t Source #

Constraint for gtraverse.

Instances

Instances details
(forall a. Generic (t a), forall a b. GTraverseRep a b f t) => GTraverse f t Source # 
Instance details

Defined in Generic.Functor.Internal

class GTraverse1 f (Default Incoherent (a -> f b)) (Rep (t a)) (Rep (t b)) => GTraverseRep a b f t Source #

Instances

Instances details
GTraverse1 f (Default Incoherent (a -> f b)) (Rep (t a)) (Rep (t b)) => GTraverseRep a b f t Source # 
Instance details

Defined in Generic.Functor.Internal

class (forall f. Applicative f => GBitraverse f t) => GTraversable t Source #

Generic Traversable.

Instances

Instances details
(forall (f :: Type -> Type). Applicative f => GBitraverse f t) => GTraversable t Source # 
Instance details

Defined in Generic.Functor.Internal

class (forall a b. Generic (t a b), forall a b c d. GBitraverseRep a b c d f t) => GBitraverse f t Source #

Constraint for gtraverse.

Instances

Instances details
(forall a b. Generic (t a b), forall a b c d. GBitraverseRep a b c d f t) => GBitraverse f t Source # 
Instance details

Defined in Generic.Functor.Internal

class GTraverse1 f (Default Incoherent ((a -> f b) :+ (c -> f d))) (Rep (t a c)) (Rep (t b d)) => GBitraverseRep a b c d f t Source #

Instances

Instances details
GTraverse1 f (Default Incoherent ((a -> f b) :+ (c -> f d))) (Rep (t a c)) (Rep (t b d)) => GBitraverseRep a b c d f t Source # 
Instance details

Defined in Generic.Functor.Internal

class (forall f. Applicative f => GBitraverse f t) => GBitraversable t Source #

Generic Bitraversable.

Instances

Instances details
(forall (f :: Type -> Type). Applicative f => GBitraverse f t) => GBitraversable t Source # 
Instance details

Defined in Generic.Functor.Internal

foldMap

class (forall a. Generic (t a), forall a b. GFoldMapRep a b m t) => GFoldMap m t Source #

Constraint for gfoldMap.

Instances

Instances details
(forall a. Generic (t a), forall a b. GFoldMapRep a b m t) => GFoldMap m t Source # 
Instance details

Defined in Generic.Functor.Internal

class GFoldMap1 m (Default Incoherent (Fold m a b)) (Rep (t a)) (Rep (t b)) => GFoldMapRep a b m t Source #

Instances

Instances details
GFoldMap1 m (Default Incoherent (Fold m a b)) (Rep (t a)) (Rep (t b)) => GFoldMapRep a b m t Source # 
Instance details

Defined in Generic.Functor.Internal

class (forall m. Monoid m => GFoldMap m t) => GFoldable t Source #

Generic Foldable. Constraint for GenericFunctor (deriving-via Foldable).

Instances

Instances details
(forall m. Monoid m => GFoldMap m t) => GFoldable t Source # 
Instance details

Defined in Generic.Functor.Internal

class (forall a b. Generic (t a b), forall a b c d. GBifoldMapRep a b c d m t) => GBifoldMap m t Source #

Constraint for gbifoldMap.

Instances

Instances details
(forall a b. Generic (t a b), forall a b c d. GBifoldMapRep a b c d m t) => GBifoldMap m t Source # 
Instance details

Defined in Generic.Functor.Internal

class GFoldMap1 m (Default Incoherent (Fold m a b :+ Fold m c d)) (Rep (t a c)) (Rep (t b d)) => GBifoldMapRep a b c d m t Source #

Instances

Instances details
GFoldMap1 m (Default Incoherent (Fold m a b :+ Fold m c d)) (Rep (t a c)) (Rep (t b d)) => GBifoldMapRep a b c d m t Source # 
Instance details

Defined in Generic.Functor.Internal

class (forall m. Monoid m => GBifoldMap m t) => GBifoldable t Source #

Generic Foldable. Constraint for GenericFunctor (deriving-via Foldable).

Instances

Instances details
(forall m. Monoid m => GBifoldMap m t) => GBifoldable t Source # 
Instance details

Defined in Generic.Functor.Internal

Others

class GMultimap (a -> b) x y => GSolomap a b x y Source #

Constraint for gsolomap.

Instances

Instances details
GMultimap (a -> b) x y => GSolomap a b x y Source # 
Instance details

Defined in Generic.Functor.Internal

class Multimap (a -> b) x y => Solomap a b x y Source #

Constraint for solomap.

Instances

Instances details
Multimap (a -> b) x y => Solomap a b x y Source # 
Instance details

Defined in Generic.Functor.Internal

class GMap1 (Default Incoherent arr) (Rep x) (Rep y) => GMultimap arr x y Source #

Constraint for gmultimap.

Instances

Instances details
GMap1 (Default Incoherent arr) (Rep x) (Rep y) => GMultimap arr x y Source # 
Instance details

Defined in Generic.Functor.Internal

class MultimapI (Default Incoherent arr) x y => Multimap arr x y Source #

Constraint for multimap.

Instances

Instances details
MultimapI (Default Incoherent arr) x y => Multimap arr x y Source # 
Instance details

Defined in Generic.Functor.Internal

Deriving Via

Functor

newtype GenericFunctor f a Source #

newtype for DerivingVia of Functor and Foldable instances.

Note: the GHC extensions DeriveFunctor, DeriveFoldable, and DeriveTraversable (which implies all three) already works out-of-the-box in most cases. There are exceptions, such as the following example.

Example

{-# LANGUAGE DeriveGeneric, DerivingVia #-}

import GHC.Generics (Generic)
import Generic.Functor (GenericFunctor(..))

data Twice a = Twice (Either a a)
  deriving Generic
  deriving (Functor, Foldable) via (GenericFunctor Twice)

Constructors

GenericFunctor (f a) 

Instances

Instances details
GFunctor f => Functor (GenericFunctor f) Source # 
Instance details

Defined in Generic.Functor.Internal

Methods

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

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

GFoldable f => Foldable (GenericFunctor f) Source # 
Instance details

Defined in Generic.Functor.Internal

Methods

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

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

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

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

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

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

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

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

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

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

null :: GenericFunctor f a -> Bool #

length :: GenericFunctor f a -> Int #

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

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

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

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

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

Bifunctor

newtype GenericBifunctor f a b Source #

newtype for DerivingVia of Bifunctor and Bifoldable instances.

Note: deriving Bifunctor for a generic type often requires Functor instances for types mentioned in the fields.

Example

{-# LANGUAGE DeriveGeneric, DerivingVia #-}

import Data.Bifoldable (Bifoldable)
import Data.Bifunctor (Bifunctor)
import GHC.Generics (Generic)
import Generic.Functor (GenericFunctor(..), GenericBifunctor(..))

data Tree a b = Node a (Tree a b) (Tree a b) | Leaf b
  deriving Generic
  deriving (Functor, Foldable) via (GenericFunctor (Tree a))
  deriving (Bifunctor, Bifoldable) via (GenericBifunctor Tree)

data CofreeF f a b = a :< f b
  deriving Generic
  deriving (Bifunctor, Bifoldable) via (GenericBifunctor (CofreeF f))

Constructors

GenericBifunctor (f a b) 

Instances

Instances details
GBifoldable f => Bifoldable (GenericBifunctor f) Source # 
Instance details

Defined in Generic.Functor.Internal

Methods

bifold :: Monoid m => GenericBifunctor f m m -> m #

bifoldMap :: Monoid m => (a -> m) -> (b -> m) -> GenericBifunctor f a b -> m #

bifoldr :: (a -> c -> c) -> (b -> c -> c) -> c -> GenericBifunctor f a b -> c #

bifoldl :: (c -> a -> c) -> (c -> b -> c) -> c -> GenericBifunctor f a b -> c #

GBifunctor f => Bifunctor (GenericBifunctor f) Source # 
Instance details

Defined in Generic.Functor.Internal

Methods

bimap :: (a -> b) -> (c -> d) -> GenericBifunctor f a c -> GenericBifunctor f b d #

first :: (a -> b) -> GenericBifunctor f a c -> GenericBifunctor f b c #

second :: (b -> c) -> GenericBifunctor f a b -> GenericBifunctor f a c #

Internal coercions

coerce1 :: Coercible s t => (r -> s) -> r -> t Source #

coerce2 :: Coercible t u => (r -> s -> t) -> r -> s -> u Source #

coerce3 :: (Coercible w v, Coercible (f b d) (g b d)) => (r -> w -> f b d) -> r -> v -> g b d Source #

coerceFoldMap :: Coercible t u => (am -> t -> m) -> am -> u -> m Source #

coerceBifoldMap :: Coercible t u => (am -> bm -> t -> m) -> am -> bm -> u -> m Source #

GMultimapK

class GMultimapK m arr f g where Source #

We use the same class to implement all of fmap, foldMap, traverse, instantiating m as Identity, 'Const (EndoM mm)' and 'Aps n' respectively. Those three cases differ in their instances for K1.

(the K stands for Kleisli, because the result is Kleisli m (f ()) (g ())

Methods

gmultimapK :: arr -> f () -> m (g ()) Source #

Instances

Instances details
GMultimapK m arr (V1 :: Type -> Type) (V1 :: Type -> Type) Source # 
Instance details

Defined in Generic.Functor.Internal

Methods

gmultimapK :: arr -> V1 () -> m (V1 ()) Source #

Applicative m => GMultimapK m arr (U1 :: Type -> Type) (U1 :: Type -> Type) Source # 
Instance details

Defined in Generic.Functor.Internal

Methods

gmultimapK :: arr -> U1 () -> m (U1 ()) Source #

(GMultimapK m arr f1 g1, GMultimapK m arr f2 g2, Applicative m) => GMultimapK m arr (f1 :*: f2) (g1 :*: g2) Source # 
Instance details

Defined in Generic.Functor.Internal

Methods

gmultimapK :: arr -> (f1 :*: f2) () -> m ((g1 :*: g2) ()) Source #

(GMultimapK m arr f1 g1, GMultimapK m arr f2 g2, Applicative m) => GMultimapK m arr (f1 :+: f2) (g1 :+: g2) Source # 
Instance details

Defined in Generic.Functor.Internal

Methods

gmultimapK :: arr -> (f1 :+: f2) () -> m ((g1 :+: g2) ()) Source #

MultimapI arr x y => GMultimapK Identity arr (K1 i x :: Type -> Type) (K1 i' y :: Type -> Type) Source # 
Instance details

Defined in Generic.Functor.Internal

Methods

gmultimapK :: arr -> K1 i x () -> Identity (K1 i' y ()) Source #

(GMultimapK m arr f g, Functor m) => GMultimapK m arr (M1 i c f) (M1 i' c' g) Source # 
Instance details

Defined in Generic.Functor.Internal

Methods

gmultimapK :: arr -> M1 i c f () -> m (M1 i' c' g ()) Source #

Multitraverse m arr x y => GMultimapK (Aps m) arr (K1 i x :: Type -> Type) (K1 i' y :: Type -> Type) Source # 
Instance details

Defined in Generic.Functor.Internal

Methods

gmultimapK :: arr -> K1 i x () -> Aps m (K1 i' y ()) Source #

GMultimapK (Const (EndoM m) :: Type -> Type) arr (K1 i x :: Type -> Type) (K1 i x :: Type -> Type) Source # 
Instance details

Defined in Generic.Functor.Internal

Methods

gmultimapK :: arr -> K1 i x () -> Const (EndoM m) (K1 i x ()) Source #

(Multifold_ m arr x y, Monoid m) => GMultimapK (Const (EndoM m) :: Type -> Type) arr (K1 i x :: Type -> Type) (K1 i' y :: Type -> Type) Source # 
Instance details

Defined in Generic.Functor.Internal

Methods

gmultimapK :: arr -> K1 i x () -> Const (EndoM m) (K1 i' y ()) Source #

Instance for fmap

class GMultimapK Identity arr f g => GMap1 arr f g Source #

Instances

Instances details
GMultimapK Identity arr f g => GMap1 arr f g Source # 
Instance details

Defined in Generic.Functor.Internal

gmapRep :: GMap1 arr f g => arr -> f () -> g () Source #

Instance for foldMap

type EndoM m = Endo (Maybe m) Source #

unEndoM :: Monoid m => EndoM m -> m Source #

liftEndoM :: Monoid m => m -> EndoM m Source #

foldToConst :: Monoid m => Fold m x y -> x -> Const (EndoM m) y Source #

class GMultimapK (Const (EndoM m)) arr f g => GFoldMap1 m arr f g Source #

Instances

Instances details
GMultimapK (Const (EndoM m) :: Type -> Type) arr f g => GFoldMap1 m arr f g Source # 
Instance details

Defined in Generic.Functor.Internal

gfoldMapRep :: forall m arr f. (GFoldMap1 m arr f f, Monoid m) => arr -> f () -> m Source #

Danger! GFoldMap1 m arr f f MUST come from a quantified constraint (see use in gfoldMap).

Instance for traverse

class GMultimapK (Aps m) arr f g => GTraverse1 m arr f g Source #

Instances

Instances details
GMultimapK (Aps m) arr f g => GTraverse1 m arr f g Source # 
Instance details

Defined in Generic.Functor.Internal

gtraverseRep :: GTraverse1 m arr f g => arr -> f () -> Aps m (g ()) Source #

Common instances