generic-functor-0.1.0.0: Deriving generalized functors with GHC.Generics

Safe HaskellNone
LanguageHaskell2010

Generic.Functor

Contents

Description

Generic and generalized functors.

Synopsis

Derive functors

Unary functors

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.

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)

N-ary functors

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)

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
Multimap_ (S arr arr') x y => Multimap_ (S arr ((a -> b) :+ arr')) x y Source # 
Instance details

Defined in Generic.Functor.Internal

Methods

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

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

Defined in Generic.Functor.Internal

Methods

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

Derive Functor and Bifunctor

DerivingVia

newtype DeriveFunctor f a Source #

newtype for DerivingVia of Functor instances.

Note: the GHC extension DeriveFunctor 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 (DeriveFunctor(..))

data Twice a = Twice (Either a a)
  deriving Generic
  deriving Functor via (DeriveFunctor Twice)

Constructors

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

Defined in Generic.Functor.Internal

Methods

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

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

newtype DeriveBifunctor f a b Source #

newtype for DerivingVia of Bifunctor instances.

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

Example

{-# LANGUAGE DeriveGeneric, DerivingVia #-}

import GHC.Generics (Generic)
import Generic.Functor (DeriveFunctor(..), DeriveBifunctor(..))

data Tree a b = Node a (Tree a b) (Tree a b) | Leaf b
  deriving Generic
  deriving Functor via (DeriveFunctor (Tree a))
  deriving Bifunctor via (DeriveBifunctor Tree)

data CofreeF f a b = a :< f b
  deriving Generic
  deriving Bifunctor via (DeriveBifunctor (CofreeF f))

Constructors

DeriveBifunctor (f a b) 
Instances
(GBifunctor f, GFirst f, GSecond f) => Bifunctor (DeriveBifunctor f) Source # 
Instance details

Defined in Generic.Functor.Internal

Methods

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

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

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

Generic method definitions

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

Generic implementation of fmap. See also DeriveFunctor 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.

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

Generic implementation of bimap. See also DeriveBifunctor.

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

Generic implementation of first. See also DeriveBifunctor.

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

Generic implementation of second. See also DeriveBifunctor.

Auxiliary classes

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

Constraint for gfmap.

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

Defined in Generic.Functor.Internal

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

Constraint for gbimap.

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

Defined in Generic.Functor.Internal

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

Constraint for gfirst.

Instances
(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 (forall a c. Generic (f a c), forall a c d. GFunctorRep c d (f a)) => GSecond f Source #

Constraint for gsecond.

Instances
(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 GMap1 ((a -> b) :+ ()) (Rep x) (Rep y) => GSolomap a b x y Source #

Constraint for gsolomap.

Instances
GMap1 ((a -> b) :+ ()) (Rep x) (Rep 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
Multimap ((a -> b) :+ ()) x y => Solomap a b x y Source # 
Instance details

Defined in Generic.Functor.Internal

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

Constraint for gmultimap.

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

Defined in Generic.Functor.Internal

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

Constraint for multimap.

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

Defined in Generic.Functor.Internal