generic-functor-1.0.0.0: Deriving generalized functors with GHC.Generics
Safe HaskellSafe-Inferred
LanguageHaskell2010

Generic.Functor.Multimap

Description

Generalized functors, where the type parameter(s) may be nested in arbitrary compositions of functors.

Note that these functions are unsafe because they rely on incoherent instances.

See the Usage section of gsolomap for details.

Example

module Main where

import Generic.Functor
import GHC.Generics (Generic)

data T a b = C Int a b
  deriving (Show, Generic)

fmapT :: (b -> b') -> T a b -> T a b'
fmapT = gsolomap

firstT :: (a -> a') -> T a b -> T a' b
firstT = gsolomap

bothT :: (a -> a') -> T a a -> T a' a'
bothT = gsolomap

watT ::
  (a -> a') ->
  T (a , a ) ((a  -> a') -> Maybe a ) ->
  T (a', a') ((a' -> a ) -> Maybe a')
watT = gsolomap

-- Incoherence test
main :: IO ()
main = do
  print (fmapT    ((+1) :: Int -> Int) (C 0 0 0 :: T Int Int))
  print (gsolomap ((+1) :: Int -> Int) (C 0 0 0 :: T Int Int) :: T Int Int)
  -- NB: Type annotations are needed on both the input and output T Int Int.
  putStrLn "We are not the same."

  -- Output:
  --     C 0 0 1
  --     C 1 1 1
  --     We are not the same.
Synopsis

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.

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)

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

Instances details
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 (NilArr :+ arr')) x y Source # 
Instance details

Defined in Generic.Functor.Internal.Implicit

Methods

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

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 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 (arr0 :+ arr')) x y Source # 
Instance details

Defined in Generic.Functor.Internal.Implicit

Methods

multimap_ :: S arr (arr0 :+ arr') -> cat x y 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 #

(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 (->) arr y1 x1, MultimapOf (->) arr x2 y2) => Multimap_ (->) (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

Generalized functors

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