| Portability | non-portable |
|---|---|
| Stability | experimental |
| Maintainer | generics@haskell.org |
Generics.EMGM.Functions.Map
Description
Summary: Generic functions that translate values of one type into values of another.
map is a generic version of the Prelude map function. It works
on all supported container datatypes of kind * -> *. The map function is
equivalent to fmap after deriving if that were possible.
Functor
cast is a generic and configurable function for converting a value of one
type into a value of another using instances provided by the programmer.
Documentation
The type of a generic function that takes a value of one type and returns a value of a different type.
map :: FRep2 Map f => (a -> b) -> f a -> f bSource
Apply a function to all elements of a container datatype (kind * -> *).
replace :: FRep2 Map f => f a -> b -> f bSource
Replace all a-values in f a with b. Defined as:
replace as b = map (const b) as
bimap :: BiFRep2 Map f => (a -> c) -> (b -> d) -> f a b -> f c dSource
Given a datatype F a b, bimap f g applies the function f :: a -> c to
every a-element and the function g :: b -> d to every b-element. The
result is a value with transformed elements: F c d.
cast :: Rep (Map a) b => a -> bSource
Cast a value of one type into a value of another. This is a configurable function that allows you to define your own type-safe conversions for a variety of types.
cast works with instances of in which you choose the
input type Rep (Map i) oi and the output type o and implement the function of type i
-> o.
Here are some examples of instances (and flags you will need or want):
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}
instanceRep(MapInt)Charwhererep=Mapchr
instanceRep(MapFloat)Doublewhererep=MaprealToFrac
instanceRep(MapInteger)Integerwhererep=Map(+42)
There are no pre-defined instances, and a call to cast will not compile if
no instances for the input and output type pair are found, so you must define
instances in order to use cast.