Haskell Hierarchical Libraries (base package)ContentsIndex
Data.Generics.Basics
Portability non-portable
Stability experimental
Maintainer libraries@haskell.org
Contents
The Data class for processing constructor applications
Constructor representations
Constructing constructor representations
Observing constructor representations
Generic maps defined in terms of gfoldl
Description
"Scrap your boilerplate" --- Generic programming in Haskell See http://www.cs.vu.nl/boilerplate/. The present module provides the Data class with its primitives for generic programming.
Synopsis
module Data.Typeable
class Typeable a => Data a where
gfoldl :: (forall a b . Data a => c (a -> b) -> a -> c b) -> (forall g . g -> c g) -> a -> c a
toConstr :: a -> Constr
fromConstr :: Constr -> a
dataTypeOf :: a -> DataType
data Constr
type ConIndex = Int
data Fixity
= Prefix
| Infix
data DataType
mkConstr :: ConIndex -> String -> Fixity -> Constr
mkDataType :: [Constr] -> DataType
conString :: Constr -> String
conFixity :: Constr -> Fixity
conIndex :: Constr -> ConIndex
stringCon :: DataType -> String -> Maybe Constr
indexCon :: DataType -> ConIndex -> Constr
maxConIndex :: DataType -> ConIndex
dataTypeCons :: DataType -> [Constr]
gmapT :: Data a => (forall b . Data b => b -> b) -> a -> a
gmapQ :: Data a => (forall a . Data a => a -> u) -> a -> [u]
gmapQl :: Data a => (r -> r' -> r) -> r -> (forall a . Data a => a -> r') -> a -> r
gmapQr :: Data a => (r' -> r -> r) -> r -> (forall a . Data a => a -> r') -> a -> r
gmapM :: (Data a, Monad m) => (forall a . Data a => a -> m a) -> a -> m a
gmapMp :: (Data a, MonadPlus m) => (forall a . Data a => a -> m a) -> a -> m a
gmapMo :: (Data a, MonadPlus m) => (forall a . Data a => a -> m a) -> a -> m a
Documentation
module Data.Typeable
The Data class for processing constructor applications
class Typeable a => Data a where
Methods
gfoldl :: (forall a b . Data a => c (a -> b) -> a -> c b) -> (forall g . g -> c g) -> a -> c a
Left-associative fold operation for constructor applications
toConstr :: a -> Constr
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).
fromConstr :: Constr -> a
Building a term from a constructor
dataTypeOf :: a -> DataType
Provide access to list of all constructors
Instances
Data Int
Data Integer
Data Float
Data Char
Data Rational
Data Bool
Data a => Data [a]
Data a => Data (Maybe a)
(Data a, Data b) => Data (a, b)
(Data a, Data b) => Data (Either a b)
(Typeable a, Typeable b) => Data (a -> b)
Constructor representations
data Constr
Representation of constructors
Instances
Eq Constr
Show Constr
Typeable Constr
type ConIndex = Int
Unique index for datatype constructors. Textual order is respected. Starts at 1.
data Fixity
Fixity of constructors
Constructors
Prefix
Infix
Instances
Eq Fixity
Show Fixity
data DataType
A package of constructor representations; could be a list, an array, a balanced tree, or others.
Instances
Show DataType
Constructing constructor representations
mkConstr :: ConIndex -> String -> Fixity -> Constr
Make a representation for a datatype constructor
mkDataType :: [Constr] -> DataType
Make a package of constructor representations
Observing constructor representations
conString :: Constr -> String
Turn a constructor into a string
conFixity :: Constr -> Fixity
Determine fixity of a constructor; undefined for primitive types.
conIndex :: Constr -> ConIndex
Determine index of a constructor. Undefined for primitive types.
stringCon :: DataType -> String -> Maybe Constr
Lookup a constructor via a string
indexCon :: DataType -> ConIndex -> Constr
Lookup a constructor by its index;
maxConIndex :: DataType -> ConIndex
Return maximum index; 0 for primitive types
dataTypeCons :: DataType -> [Constr]
Return all constructors in increasing order of indicies; empty list for primitive types
Generic maps defined in terms of gfoldl
gmapT :: Data a => (forall b . Data b => b -> b) -> a -> a
A generic transformation that maps over the immediate subterms
gmapQ :: Data a => (forall a . Data a => a -> u) -> a -> [u]
A generic query that processes the immediate subterms and returns a list
gmapQl :: Data a => (r -> r' -> r) -> r -> (forall a . Data a => a -> r') -> a -> r
A generic query with a left-associative binary operator
gmapQr :: Data a => (r' -> r -> r) -> r -> (forall a . Data a => a -> r') -> a -> r
A generic query with a right-associative binary operator
gmapM :: (Data a, Monad m) => (forall a . Data a => a -> m a) -> a -> m a
A generic monadic transformation that maps over the immediate subterms
gmapMp :: (Data a, MonadPlus m) => (forall a . Data a => a -> m a) -> a -> m a
Transformation of at least one immediate subterm does not fail
gmapMo :: (Data a, MonadPlus m) => (forall a . Data a => a -> m a) -> a -> m a
Transformation of one immediate subterm with success
Produced by Haddock version 0.6