| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Generic.Functor
Contents
Description
Generic and generalized functors.
Synopsis
- gsolomap :: forall a b x y. (Generic x, Generic y, GSolomap a b x y) => (a -> b) -> x -> y
- solomap :: forall a b x y. Solomap a b x y => (a -> b) -> x -> y
- newtype DeriveFunctor f a = DeriveFunctor (f a)
- gfmap :: forall f a b. GFunctor f => (a -> b) -> f a -> f b
- class (forall a. Generic (f a), forall a b. GFunctorRep a b f) => GFunctor f
- class GMap1 a b (Rep x) (Rep y) => GSolomap a b x y
- class Solomap_ a b x y => Solomap a b x y
Derive 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.)
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 .
Under the above conditions, that law and the types should uniquely determine
the implementation, which gsolomap id = idgsolomap 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)
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:
{-# 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 # | |
Defined in Generic.Functor.Internal Methods fmap :: (a -> b) -> DeriveFunctor f a -> DeriveFunctor f b # (<$) :: a -> DeriveFunctor f b -> DeriveFunctor f a # | |
gfmap :: forall f a b. GFunctor f => (a -> b) -> f a -> f b Source #
Generic implementation of fmap. See also DeriveFunctor for deriving-via,
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
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 # | |
Defined in Generic.Functor.Internal | |