bifunctors-5.2: Bifunctors

Copyright(C) 2008-2016 Edward Kmett, (C) 2015 Ryan Scott
LicenseBSD-style (see the file LICENSE)
MaintainerEdward Kmett <ekmett@gmail.com>
Stabilityprovisional
Portabilityportable
Safe HaskellNone
LanguageHaskell98

Data.Bifunctor.TH

Contents

Description

Functions to mechanically derive Bifunctor, Bifoldable, or Bitraversable instances, or to splice their functions directly into source code. You need to enable the TemplateHaskell language extension in order to use this module.

Synopsis

derive- functions

deriveBifunctor, deriveBifoldable, and deriveBitraversable automatically generate their respective class instances for a given data type, newtype, or data family instance that has at least two type variable. Examples:

{-# LANGUAGE TemplateHaskell #-}
import Data.Bifunctor.TH

data Pair a b = Pair a b
$(deriveBifunctor ''Pair) -- instance Bifunctor Pair where ...

data WrapLeftPair f g a b = WrapLeftPair (f a) (g a b)
$(deriveBifoldable ''WrapLeftPair)
-- instance (Foldable f, Bifoldable g) => Bifoldable (WrapLeftPair f g) where ...

If you are using template-haskell-2.7.0.0 or later (i.e., GHC 7.4 or later), the derive functions can be used data family instances (which requires the -XTypeFamilies extension). To do so, pass the name of a data or newtype instance constructor (NOT a data family name!) to a derive function. Note that the generated code may require the -XFlexibleInstances extension. Example:

{-# LANGUAGE FlexibleInstances, TemplateHaskell, TypeFamilies #-}
import Data.Bifunctor.TH

class AssocClass a b c where
    data AssocData a b c
instance AssocClass Int b c where
    data AssocData Int b c = AssocDataInt1 Int | AssocDataInt2 b c
$(deriveBitraversable 'AssocDataInt1) -- instance Bitraversable (AssocData Int) where ...
-- Alternatively, one could use $(deriveBitraversable 'AssocDataInt2)

Note that there are some limitations:

  • The Name argument to a derive function must not be a type synonym.
  • With a derive function, the last two type variables must both be of kind *. Other type variables of kind * -> * are assumed to require a Functor, Foldable, or Traversable constraint (depending on which derive function is used), and other type variables of kind * -> * -> * are assumed to require an Bifunctor, Bifoldable, or Bitraversable constraint. If your data type doesn't meet these assumptions, use a make function.
  • If using the -XDatatypeContexts, -XExistentialQuantification, or -XGADTs extensions, a constraint cannot mention either of the last two type variables. For example, data Illegal2 a b where I2 :: Ord a => a -> b -> Illegal2 a b cannot have a derived Bifunctor instance.
  • If either of the last two type variables is used within a constructor argument's type, it must only be used in the last two type arguments. For example, data Legal a b = Legal (Int, Int, a, b) can have a derived Bifunctor instance, but data Illegal a b = Illegal (a, b, a, b) cannot.
  • Data family instances must be able to eta-reduce the last two type variables. In other words, if you have a instance of the form:
 data family Family a1 ... an t1 t2
 data instance Family e1 ... e2 v1 v2 = ...
 

Then the following conditions must hold:

  1. v1 and v2 must be distinct type variables.
  2. Neither v1 not v2 must be mentioned in any of e1, ..., e2.
  • In GHC 7.8, a bug exists that can cause problems when a data family declaration and one of its data instances use different type variables, e.g.,
 data family Foo a b c
 data instance Foo Int y z = Foo Int y z
 $(deriveBifunctor 'Foo)
 

To avoid this issue, it is recommened that you use the same type variables in the same positions in which they appeared in the data family declaration:

 data family Foo a b c
 data instance Foo Int b c = Foo Int b c
 $(deriveBifunctor 'Foo)
 

deriveBifunctor :: Name -> Q [Dec]

Generates a Bifunctor instance declaration for the given data type or data family instance.

makeBimap :: Name -> Q Exp

Generates a lambda expression which behaves like bimap (without requiring a Bifunctor instance).

Bifoldable

deriveBifoldable :: Name -> Q [Dec]

Generates a Bifoldable instance declaration for the given data type or data family instance.

makeBifold :: Name -> Q Exp

Generates a lambda expression which behaves like bifold (without requiring a Bifoldable instance).

makeBifoldMap :: Name -> Q Exp

Generates a lambda expression which behaves like bifoldMap (without requiring a Bifoldable instance).

makeBifoldr :: Name -> Q Exp

Generates a lambda expression which behaves like bifoldr (without requiring a Bifoldable instance).

makeBifoldl :: Name -> Q Exp

Generates a lambda expression which behaves like bifoldl (without requiring a Bifoldable instance).

Bitraversable

deriveBitraversable :: Name -> Q [Dec]

Generates a Bitraversable instance declaration for the given data type or data family instance.

makeBitraverse :: Name -> Q Exp

Generates a lambda expression which behaves like bitraverse (without requiring a Bitraversable instance).

makeBisequenceA :: Name -> Q Exp

Generates a lambda expression which behaves like bisequenceA (without requiring a Bitraversable instance).

makeBimapM :: Name -> Q Exp

Generates a lambda expression which behaves like bimapM (without requiring a Bitraversable instance).

makeBisequence :: Name -> Q Exp

Generates a lambda expression which behaves like bisequence (without requiring a Bitraversable instance).