Copyright | (c) The University of Glasgow CWI 2001--2004 |
---|---|
License | BSD-style (see the file libraries/base/LICENSE) |
Maintainer | [email protected] |
Stability | experimental |
Portability | non-portable (local universal quantification) |
Safe Haskell | Trustworthy |
Language | Haskell2010 |
"Scrap your boilerplate" --- Generic programming in Haskell. See http://www.haskell.org/haskellwiki/Research_papers/Generics#Scrap_your_boilerplate.21. This module provides the Data
class with its primitives for generic programming, along with instances for many datatypes. It corresponds to a merge between the previous Data.Generics.Basics and almost all of Data.Generics.Instances. The instances that are not present in this module were moved to the Data.Generics.Instances
module in the syb
package.
For more information, please visit the new SYB wiki: http://www.cs.uu.nl/wiki/bin/view/GenericProgramming/SYB.
module Data.Typeable
class Typeable a => Data a where Source
The Data
class comprehends a fundamental primitive gfoldl
for folding over constructor applications, say terms. This primitive can be instantiated in several ways to map over the immediate subterms of a term; see the gmap
combinators later in this class. Indeed, a generic programmer does not necessarily need to use the ingenious gfoldl primitive but rather the intuitive gmap
combinators. The gfoldl
primitive is completed by means to query top-level constructors, to turn constructor representations into proper terms, and to list all possible datatype constructors. This completion allows us to serve generic programming scenarios like read, show, equality, term generation.
The combinators gmapT
, gmapQ
, gmapM
, etc are all provided with default definitions in terms of gfoldl
, leaving open the opportunity to provide datatype-specific definitions. (The inclusion of the gmap
combinators as members of class Data
allows the programmer or the compiler to derive specialised, and maybe more efficient code per datatype. Note: gfoldl
is more higher-order than the gmap
combinators. This is subject to ongoing benchmarking experiments. It might turn out that the gmap
combinators will be moved out of the class Data
.)
Conceptually, the definition of the gmap
combinators in terms of the primitive gfoldl
requires the identification of the gfoldl
function arguments. Technically, we also need to identify the type constructor c
for the construction of the result type from the folded term type.
In the definition of gmapQ
x combinators, we use phantom type constructors for the c
in the type of gfoldl
because the result type of a query does not involve the (polymorphic) type of the term argument. In the definition of gmapQl
we simply use the plain constant type constructor because gfoldl
is left-associative anyway and so it is readily suited to fold a left-associative binary operation over the immediate subterms. In the definition of gmapQr, extra effort is needed. We use a higher-order accumulation trick to mediate between left-associative constructor application vs. right-associative binary operation (e.g., (:)
). When the query is meant to compute a value of type r
, then the result type withing generic folding is r -> r
. So the result of folding is a function to which we finally pass the right unit.
With the -XDeriveDataTypeable
option, GHC can generate instances of the Data
class automatically. For example, given the declaration
data T a b = C1 a b | C2 deriving (Typeable, Data)
GHC will generate an instance that is equivalent to
instance (Data a, Data b) => Data (T a b) where gfoldl k z (C1 a b) = z C1 `k` a `k` b gfoldl k z C2 = z C2 gunfold k z c = case constrIndex c of 1 -> k (k (z C1)) 2 -> z C2 toConstr (C1 _ _) = con_C1 toConstr C2 = con_C2 dataTypeOf _ = ty_T con_C1 = mkConstr ty_T "C1" [] Prefix con_C2 = mkConstr ty_T "C2" [] Prefix ty_T = mkDataType "Module.T" [con_C1, con_C2]
This is suitable for datatypes that are exported transparently.
:: (forall d b. Data d => c (d -> b) -> d -> c b) | defines how nonempty constructor applications are folded. It takes the folded tail of the constructor application and its head, i.e., an immediate subterm, and combines them in some way. |
-> (forall g. g -> c g) | defines how the empty constructor application is folded, like the neutral / start element for list folding. |
-> a | structure to be folded. |
-> c a | result, with a type defined in terms of |
Left-associative fold operation for constructor applications.
The type of gfoldl
is a headache, but operationally it is a simple generalisation of a list fold.
The default definition for gfoldl
is const id
, which is suitable for abstract datatypes with no substructures.
gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c a Source
Unfolding constructor applications
toConstr :: a -> Constr Source
Obtaining the constructor from a given datum. For proper terms, this is meant to be the top-level constructor. Primitive datatypes are here viewed as potentially infinite sets of values (i.e., constructors).
dataTypeOf :: a -> DataType Source
The outer type constructor of the type
dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c a) Source
Mediate types and unary type constructors. In Data
instances of the form T a
, dataCast1
should be defined as gcast1
.
The default definition is const Nothing
, which is appropriate for non-unary type constructors.
dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a) Source
Mediate types and binary type constructors. In Data
instances of the form T a b
, dataCast2
should be defined as gcast2
.
The default definition is const Nothing
, which is appropriate for non-binary type constructors.
gmapT :: (forall b. Data b => b -> b) -> a -> a Source
A generic transformation that maps over the immediate subterms
The default definition instantiates the type constructor c
in the type of gfoldl
to an identity datatype constructor, using the isomorphism pair as injection and projection.
gmapQl :: forall r r'. (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r Source
A generic query with a left-associative binary operator
gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r Source
A generic query with a right-associative binary operator
gmapQ :: (forall d. Data d => d -> u) -> a -> [u] Source
A generic query that processes the immediate subterms and returns a list of results. The list is given in the same order as originally specified in the declaration of the data constructors.
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> a -> u Source
A generic query that processes one child by index (zero-based)
gmapM :: forall m. Monad m => (forall d. Data d => d -> m d) -> a -> m a Source
A generic monadic transformation that maps over the immediate subterms
The default definition instantiates the type constructor c
in the type of gfoldl
to the monad datatype constructor, defining injection and projection using return
and >>=
.
gmapMp :: forall m. MonadPlus m => (forall d. Data d => d -> m d) -> a -> m a Source
Transformation of at least one immediate subterm does not fail
gmapMo :: forall m. MonadPlus m => (forall d. Data d => d -> m d) -> a -> m a Source
Transformation of one immediate subterm with success
Data Bool | Since: 4.0.0.0 |
Data Char | Since: 4.0.0.0 |
Data Double | Since: 4.0.0.0 |
Data Float | Since: 4.0.0.0 |
Data Int | Since: 4.0.0.0 |
Data Int8 | Since: 4.0.0.0 |
Data Int16 | Since: 4.0.0.0 |
Data Int32 | Since: 4.0.0.0 |
Data Int64 | Since: 4.0.0.0 |
Data Integer | Since: 4.0.0.0 |
Data Natural | Since: 4.8.0.0 |
Data Ordering | Since: 4.0.0.0 |
Data Word | Since: 4.0.0.0 |
Data Word8 | Since: 4.0.0.0 |
Data Word16 | Since: 4.0.0.0 |
Data Word32 | Since: 4.0.0.0 |
Data Word64 | Since: 4.0.0.0 |
Data () | Since: 4.0.0.0 |
Data DecidedStrictness | Since: 4.9.0.0 |
Data SourceStrictness | Since: 4.9.0.0 |
Data SourceUnpackedness | Since: 4.9.0.0 |
Data Associativity | Since: 4.9.0.0 |
Data Fixity | Since: 4.9.0.0 |
Data Any | Since: 4.8.0.0 |
Data All | Since: 4.8.0.0 |
Data Version | Since: 4.7.0.0 |
Data SpecConstrAnnotation | |
Data Void | |
Data a => Data [a] | Since: 4.0.0.0 |
Data a => Data (Maybe a) | Since: 4.0.0.0 |
(Data a, Integral a) => Data (Ratio a) | Since: 4.0.0.0 |
Data a => Data (Ptr a) | Since: 4.8.0.0 |
Data p => Data (Par1 p) | Since: 4.9.0.0 |
Data a => Data (Last a) | Since: 4.8.0.0 |
Data a => Data (First a) | Since: 4.8.0.0 |
Data a => Data (Product a) | Since: 4.8.0.0 |
Data a => Data (Sum a) | Since: 4.8.0.0 |
Data a => Data (Dual a) | Since: 4.8.0.0 |
Data a => Data (ForeignPtr a) | Since: 4.8.0.0 |
Data a => Data (Identity a) | Since: 4.9.0.0 |
Data a => Data (NonEmpty a) | |
Data a => Data (Option a) | |
Data m => Data (WrappedMonoid m) | |
Data a => Data (Last a) | |
Data a => Data (First a) | |
Data a => Data (Max a) | |
Data a => Data (Min a) | |
Typeable * a => Data (Fixed a) | Since: 4.1.0.0 |
Data a => Data (Complex a) | |
(Data a, Data b) => Data (Either a b) | Since: 4.0.0.0 |
Data p => Data (V1 * p) | Since: 4.9.0.0 |
Data p => Data (U1 * p) | Since: 4.9.0.0 |
(Data a, Data b) => Data (a, b) | Since: 4.0.0.0 |
Data t => Data (Proxy * t) | Since: 4.7.0.0 |
(Data b, Data a) => Data (Arg a b) | |
(Data (f p), Typeable (* -> *) f, Data p) => Data (Rec1 * f p) | Since: 4.9.0.0 |
(Data a, Data b, Data c) => Data (a, b, c) | Since: 4.0.0.0 |
((~) * a b, Data a) => Data ((:~:) * a b) | Since: 4.7.0.0 |
(Coercible * a b, Data a, Data b) => Data (Coercion * a b) | Since: 4.7.0.0 |
(Data (f a), Data a, Typeable (* -> *) f) => Data (Alt * f a) | Since: 4.8.0.0 |
(Typeable * k3, Data a, Typeable k3 b) => Data (Const k3 a b) | Since: 4.10.0.0 |
(Typeable * i, Data p, Data c) => Data (K1 * i c p) | Since: 4.9.0.0 |
(Typeable (* -> *) f, Typeable (* -> *) g, Data p, Data (f p), Data (g p)) => Data ((:+:) * f g p) | Since: 4.9.0.0 |
(Typeable (* -> *) f, Typeable (* -> *) g, Data p, Data (f p), Data (g p)) => Data ((:*:) * f g p) | Since: 4.9.0.0 |
(Data a, Data b, Data c, Data d) => Data (a, b, c, d) | Since: 4.0.0.0 |
(Typeable * i2, Typeable * j2, Typeable i2 a, Typeable j2 b, (~~) i2 j2 a b) => Data ((:~~:) i2 j2 a b) | Since: 4.10.0.0 |
(Data (g a), Data (f a), Typeable * k, Typeable (k -> *) g, Typeable (k -> *) f, Typeable k a) => Data (Sum k f g a) | |
(Data (g a), Data (f a), Typeable * k, Typeable (k -> *) g, Typeable (k -> *) f, Typeable k a) => Data (Product k f g a) | |
(Data p, Data (f p), Typeable Meta c, Typeable * i, Typeable (* -> *) f) => Data (M1 * i c f p) | Since: 4.9.0.0 |
(Typeable (* -> *) f, Typeable (* -> *) g, Data p, Data (f (g p))) => Data ((:.:) * * f g p) | Since: 4.9.0.0 |
(Data a, Data b, Data c, Data d, Data e) => Data (a, b, c, d, e) | Since: 4.0.0.0 |
(Data (f (g a)), Typeable * k2, Typeable * k1, Typeable (k2 -> k1) g, Typeable (k1 -> *) f, Typeable k2 a) => Data (Compose k1 k2 f g a) | |
(Data a, Data b, Data c, Data d, Data e, Data f) => Data (a, b, c, d, e, f) | Since: 4.0.0.0 |
(Data a, Data b, Data c, Data d, Data e, Data f, Data g) => Data (a, b, c, d, e, f, g) | Since: 4.0.0.0 |
Representation of datatypes. A package of constructor representations with names of type and module.
mkDataType :: String -> [Constr] -> DataType Source
Constructs an algebraic datatype
mkIntType :: String -> DataType Source
Constructs the Int
type
mkFloatType :: String -> DataType Source
Constructs the Float
type
mkCharType :: String -> DataType Source
Constructs the Char
type
mkNoRepType :: String -> DataType Source
Constructs a non-representation for a non-representable type
dataTypeName :: DataType -> String Source
Gets the type constructor including the module
Public representation of datatypes
dataTypeRep :: DataType -> DataRep Source
Gets the public presentation of a datatype
repConstr :: DataType -> ConstrRep -> Constr Source
Look up a constructor by its representation
isAlgType :: DataType -> Bool Source
Test for an algebraic type
dataTypeConstrs :: DataType -> [Constr] Source
Gets the constructors of an algebraic datatype
indexConstr :: DataType -> ConIndex -> Constr Source
Gets the constructor for an index (algebraic datatypes only)
maxConstrIndex :: DataType -> ConIndex Source
Gets the maximum constructor index of an algebraic datatype
isNorepType :: DataType -> Bool Source
Test for a non-representable type
Representation of constructors. Note that equality on constructors with different types may not work -- i.e. the constructors for False
and Nothing
may compare equal.
Unique index for datatype constructors, counting from 1 in the order they are given in the program text.
Fixity of constructors
mkConstr :: DataType -> String -> [String] -> Fixity -> Constr Source
Constructs a constructor
mkIntegralConstr :: (Integral a, Show a) => DataType -> a -> Constr Source
mkRealConstr :: (Real a, Show a) => DataType -> a -> Constr Source
mkCharConstr :: DataType -> Char -> Constr Source
Makes a constructor for Char
.
constrType :: Constr -> DataType Source
Gets the datatype of a constructor
Public representation of constructors
AlgConstr ConIndex | |
IntConstr Integer | |
FloatConstr Rational | |
CharConstr Char |
constrRep :: Constr -> ConstrRep Source
Gets the public presentation of constructors
constrFields :: Constr -> [String] Source
Gets the field labels of a constructor. The list of labels is returned in the same order as they were given in the original constructor declaration.
constrFixity :: Constr -> Fixity Source
Gets the fixity of a constructor
constrIndex :: Constr -> ConIndex Source
Gets the index of a constructor (algebraic datatypes only)
showConstr :: Constr -> String Source
Gets the string for a constructor
readConstr :: DataType -> String -> Maybe Constr Source
Lookup a constructor via a string
tyconUQname :: String -> String Source
Gets the unqualified type constructor: drop *.*.*... before name
tyconModule :: String -> String Source
Gets the module of a type constructor: take *.*.*... before name
fromConstr :: Data a => Constr -> a Source
Build a term skeleton
fromConstrB :: Data a => (forall d. Data d => d) -> Constr -> a Source
Build a term and use a generic function for subterms
fromConstrM :: forall m a. (Monad m, Data a) => (forall d. Data d => m d) -> Constr -> m a Source
Monadic variation on fromConstrB
© The University of Glasgow and others
Licensed under a BSD-style license (see top of the page).
https://downloads.haskell.org/~ghc/8.2.1/docs/html/libraries/base-4.10.0.0/Data-Data.html