bifunctors-5.5.4: Bifunctors

Copyright(C) 2008-2016 Edward Kmett (C) 2015-2016 Ryan Scott
LicenseBSD-style (see the file LICENSE)
MaintainerEdward Kmett <ekmett@gmail.com>
Stabilityprovisional
Portabilityportable
Safe HaskellUnsafe
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.

There may be scenarios in which you want to, say, bimap over an arbitrary data type or data family instance without having to make the type an instance of Bifunctor. For these cases, this module provides several functions (all prefixed with make-) that splice the appropriate lambda expression into your source code.

This is particularly useful for creating instances for sophisticated data types. For example, deriveBifunctor cannot infer the correct type context for newtype HigherKinded f a b c = HigherKinded (f a b c), since f is of kind * -> * -> * -> *. However, it is still possible to create a Bifunctor instance for HigherKinded without too much trouble using makeBimap:

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

newtype HigherKinded f a b c = HigherKinded (f a b c)

instance Bifunctor (f a) => Bifunctor (HigherKinded f a) where
    bimap = $(makeBimap ''HigherKinded)

deriveBifunctor :: Name -> Q [Dec] Source #

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

deriveBifunctorOptions :: Options -> Name -> Q [Dec] Source #

Like deriveBifunctor, but takes an Options argument.

makeBimap :: Name -> Q Exp Source #

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

makeBimapOptions :: Options -> Name -> Q Exp Source #

Like makeBimap, but takes an Options argument.

Bifoldable

deriveBifoldable :: Name -> Q [Dec] Source #

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

deriveBifoldableOptions :: Options -> Name -> Q [Dec] Source #

Like deriveBifoldable, but takes an Options argument.

makeBifoldOptions :: Options -> Name -> Q Exp Source #

Like makeBifold, but takes an Options argument.

makeBifoldMap :: Name -> Q Exp Source #

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

makeBifoldMapOptions :: Options -> Name -> Q Exp Source #

Like makeBifoldMap, but takes an Options argument.

makeBifoldr :: Name -> Q Exp Source #

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

makeBifoldrOptions :: Options -> Name -> Q Exp Source #

Like makeBifoldr, but takes an Options argument.

makeBifoldl :: Name -> Q Exp Source #

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

makeBifoldlOptions :: Options -> Name -> Q Exp Source #

Like makeBifoldl, but takes an Options argument.

Bitraversable

deriveBitraversable :: Name -> Q [Dec] Source #

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

makeBitraverse :: Name -> Q Exp Source #

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

makeBitraverseOptions :: Options -> Name -> Q Exp Source #

Like makeBitraverse, but takes an Options argument.

makeBisequenceA :: Name -> Q Exp Source #

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

makeBisequenceAOptions :: Options -> Name -> Q Exp Source #

Like makeBitraverseA, but takes an Options argument.

makeBimapM :: Name -> Q Exp Source #

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

makeBimapMOptions :: Options -> Name -> Q Exp Source #

Like makeBimapM, but takes an Options argument.

makeBisequence :: Name -> Q Exp Source #

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

makeBisequenceOptions :: Options -> Name -> Q Exp Source #

Like makeBisequence, but takes an Options argument.

Options

newtype Options Source #

Options that further configure how the functions in Data.Bifunctor.TH should behave.

Constructors

Options 

Fields

  • emptyCaseBehavior :: Bool

    If True, derived instances for empty data types (i.e., ones with no data constructors) will use the EmptyCase language extension. If False, derived instances will simply use seq instead. (This has no effect on GHCs before 7.8, since EmptyCase is only available in 7.8 or later.)

Instances
Eq Options Source # 
Instance details

Defined in Data.Bifunctor.TH

Methods

(==) :: Options -> Options -> Bool #

(/=) :: Options -> Options -> Bool #

Ord Options Source # 
Instance details

Defined in Data.Bifunctor.TH

Read Options Source # 
Instance details

Defined in Data.Bifunctor.TH

Show Options Source # 
Instance details

Defined in Data.Bifunctor.TH

defaultOptions :: Options Source #

Conservative Options that doesn't attempt to use EmptyCase (to prevent users from having to enable that extension at use sites.)