syb-0.7.2.4: Scrap Your Boilerplate
Copyright(c) The University of Glasgow CWI 2001--2004
LicenseBSD-style (see the LICENSE file)
Maintainergenerics@haskell.org
Stabilityexperimental
Portabilitynon-portable (local universal quantification)
Safe HaskellSafe-Inferred
LanguageHaskell98

Data.Generics.Aliases

Description

This module provides a number of declarations for typical generic function types, corresponding type case, and others.

Synopsis

Combinators which create generic functions via cast

Other programming languages sometimes provide an operator instanceof which can check whether an expression is an instance of a given type. This operator allows programmers to implement a function f :: forall a. a -> a which exhibits a different behaviour depending on whether a Bool or a Char is passed. In Haskell this is not the case: A function with type forall a. a -> a can only be the identity function or a function which loops indefinitely or throws an exception. That is, it must implement exactly the same behaviour for any type at which it is used. But sometimes it is very useful to have a function which can accept (almost) any type and exhibit a different behaviour for different types. Haskell provides this functionality with the Typeable typeclass, whose instances can be automatically derived by GHC for almost all types. This typeclass allows the definition of a functon cast which has type forall a b. (Typeable a, Typeable b) => a -> Maybe b. The cast function allows to implement a polymorphic function with different behaviour at different types:

>>> cast True :: Maybe Bool
Just True
>>> cast True :: Maybe Int
Nothing

This section provides combinators which make use of cast internally to provide various polymorphic functions with type-specific behaviour.

Transformations

mkT Source #

Arguments

:: (Typeable a, Typeable b) 
=> (b -> b)

The type-specific transformation

-> a

The argument we try to cast to type b

-> a 

Extend the identity function with a type-specific transformation. The function created by mkT ext behaves like the identity function on all arguments which cannot be cast to type b, and like the function ext otherwise. The name mkT is short for "make transformation".

Examples

Expand
>>> mkT not True
False
>>> mkT not 'a'
'a'

Since: 0.1.0.0

extT Source #

Arguments

:: (Typeable a, Typeable b) 
=> (a -> a)

The transformation we want to extend

-> (b -> b)

The type-specific transformation

-> a

The argument we try to cast to type b

-> a 

Extend a generic transformation by a type-specific transformation. The function created by extT def ext behaves like the generic transformation def if its argument cannot be cast to the type b, and like the type-specific transformation ext otherwise. The name extT is short for "extend transformation".

Examples

Expand
>>> extT id not True
False
>>> extT id not 'a'
'a'

Since: 0.1.0.0

Queries

mkQ Source #

Arguments

:: (Typeable a, Typeable b) 
=> r

The default result

-> (b -> r)

The transformation to apply if the cast is successful

-> a

The argument we try to cast to type b

-> r 

The function created by mkQ def f returns the default result def if its argument cannot be cast to type b, otherwise it returns the result of applying f to its argument. The name mkQ is short for "make query".

Examples

Expand
>>> mkQ "default" (show :: Bool -> String) True
"True"
>>> mkQ "default" (show :: Bool -> String) ()
"default"

Since: 0.1.0.0

extQ Source #

Arguments

:: (Typeable a, Typeable b) 
=> (a -> r)

The query we want to extend

-> (b -> r)

The type-specific query

-> a

The argument we try to cast to type b

-> r 

Extend a generic query by a type-specific query. The function created by extQ def ext behaves like the generic query def if its argument cannot be cast to the type b, and like the type-specific query ext otherwise. The name extQ is short for "extend query".

Examples

Expand
>>> extQ (const True) not True
False
>>> extQ (const True) not 'a'
True

Since: 0.1.0.0

Monadic transformations

mkM Source #

Arguments

:: (Monad m, Typeable a, Typeable b) 
=> (b -> m b)

The type-specific monadic transformation

-> a

The argument we try to cast to type b

-> m a 

Extend the default monadic action pure :: Monad m => a -> m a by a type-specific monadic action. The function created by mkM act behaves like pure if its argument cannot be cast to type b, and like the monadic action act otherwise. The name mkM is short for "make monadic transformation".

Examples

Expand
>>> mkM (\x -> [x, not x]) True
[True,False]
>>> mkM (\x -> [x, not x]) (5 :: Int)
[5]

Since: 0.1.0.0

extM Source #

Arguments

:: (Monad m, Typeable a, Typeable b) 
=> (a -> m a)

The monadic transformation we want to extend

-> (b -> m b)

The type-specific monadic transformation

-> a

The argument we try to cast to type b

-> m a 

Extend a generic monadic transformation by a type-specific case. The function created by extM def ext behaves like the monadic transformation def if its argument cannot be cast to type b, and like the monadic transformation ext otherwise. The name extM is short for "extend monadic transformation".

Examples

Expand
>>> extM (\x -> [x,x])(\x -> [not x, x]) True
[False,True]
>>> extM (\x -> [x,x])(\x -> [not x, x]) (5 :: Int)
[5,5]

Since: 0.1.0.0

MonadPlus transformations

mkMp Source #

Arguments

:: (MonadPlus m, Typeable a, Typeable b) 
=> (b -> m b)

The type-specific MonadPlus action

-> a

The argument we try to cast to type b

-> m a 

Extend the default MonadPlus action const mzero by a type-specific MonadPlus action. The function created by mkMp act behaves like const mzero if its argument cannot be cast to type b, and like the monadic action act otherwise. The name mkMp is short for "make MonadPlus transformation".

Examples

Expand
>>> mkMp (\x -> Just (not x)) True
Just False
>>> mkMp (\x -> Just (not x)) 'a'
Nothing

Since: 0.1.0.0

extMp Source #

Arguments

:: (MonadPlus m, Typeable a, Typeable b) 
=> (a -> m a)

The MonadPlus transformation we want to extend

-> (b -> m b)

The type-specific MonadPlus transformation

-> a

The argument we try to cast to type b

-> m a 

Extend a generic MonadPlus transformation by a type-specific case. The function created by extMp def ext behaves like MonadPlus transformation def if its argument cannot be cast to type b, and like the transformation ext otherwise. Note that extMp behaves exactly like extM. The name extMp is short for "extend MonadPlus transformation".

Examples

Expand
>>> extMp (\x -> [x,x])(\x -> [not x, x]) True
[False,True]
>>> extMp (\x -> [x,x])(\x -> [not x, x]) (5 :: Int)
[5,5]

Since: 0.1.0.0

Readers

mkR Source #

Arguments

:: (MonadPlus m, Typeable a, Typeable b) 
=> m b

The type-specific reader

-> m a 

Make a generic reader from a type-specific case. The function created by mkR f behaves like the reader f if an expression of type a can be cast to type b, and like the expression mzero otherwise. The name mkR is short for "make reader".

Examples

Expand
>>> mkR (Just True) :: Maybe Bool
Just True
>>> mkR (Just True) :: Maybe Int
Nothing

Since: 0.1.0.0

extR Source #

Arguments

:: (Monad m, Typeable a, Typeable b) 
=> m a

The generic reader we want to extend

-> m b

The type-specific reader

-> m a 

Extend a generic reader by a type-specific case. The reader created by extR def ext behaves like the reader def if expressions of type b cannot be cast to type a, and like the reader ext otherwise. The name extR is short for "extend reader".

Examples

Expand
>>> extR (Just True) (Just 'a')
Just True
>>> extR (Just True) (Just False)
Just False

Since: 0.1.0.0

Builders

extB Source #

Arguments

:: (Typeable a, Typeable b) 
=> a

The default result

-> b

The argument we try to cast to type a

-> a 

Extend a generic builder by a type-specific case. The builder created by extB def ext returns def if ext cannot be cast to type a, and like ext otherwise. The name extB is short for "extend builder".

Examples

Expand
>>> extB True 'a'
True
>>> extB True False
False

Since: 0.1.0.0

Other

ext0 :: (Typeable a, Typeable b) => c a -> c b -> c a Source #

Flexible type extension

Examples

Expand
>>> ext0 [1 :: Int, 2, 3] [True, False] :: [Int]
[1,2,3]
>>> ext0 [1 :: Int, 2, 3] [4 :: Int, 5, 6] :: [Int]
[4,5,6]

Since: 0.1.0.0

Types for generic functions

Transformations

type GenericT = forall a. Data a => a -> a Source #

Generic transformations, i.e., take an "a" and return an "a"

Since: 0.1.0.0

newtype GenericT' Source #

The type synonym GenericT has a polymorphic type, and can therefore not appear in places where monomorphic types are expected, for example in a list. The newtype GenericT` wraps GenericT in a newtype to lift this restriction.

Since: 0.1.0.0

Constructors

GT 

Fields

Queries

type GenericQ r = forall a. Data a => a -> r Source #

Generic queries of type "r", i.e., take any "a" and return an "r"

Since: 0.1.0.0

newtype GenericQ' r Source #

The type synonym GenericQ has a polymorphic type, and can therefore not appear in places where monomorphic types are expected, for example in a list. The newtype GenericQ` wraps GenericQ in a newtype to lift this restriction.

Since: 0.1.0.0

Constructors

GQ 

Fields

Monadic transformations

type GenericM m = forall a. Data a => a -> m a Source #

Generic monadic transformations, i.e., take an "a" and compute an "a"

Since: 0.1.0.0

newtype GenericM' m Source #

The type synonym GenericM has a polymorphic type, and can therefore not appear in places where monomorphic types are expected, for example in a list. The newtype GenericM` wraps GenericM in a newtype to lift this restriction.

Since: 0.1.0.0

Constructors

GM 

Fields

Readers

type GenericR m = forall a. Data a => m a Source #

Generic readers, say monadic builders, i.e., produce an "a" with the help of a monad "m".

Since: 0.1.0.0

Builders

type GenericB = forall a. Data a => a Source #

Generic builders i.e., produce an "a".

Since: 0.1.0.0

Other

type Generic c = forall a. Data a => a -> c a Source #

The general scheme underlying generic functions assumed by gfoldl; there are isomorphisms such as GenericT = Generic T.

Since: 0.1.0.0

data Generic' c Source #

The type synonym Generic has a polymorphic type, and can therefore not appear in places where monomorphic types are expected, for example in a list. The data type Generic` wraps Generic in a data type to lift this restriction.

Since: 0.1.0.0

Constructors

Generic' 

Fields

Ingredients of generic functions

orElse :: Maybe a -> Maybe a -> Maybe a Source #

Left-biased choice on maybes

Examples

Expand
>>> orElse Nothing Nothing
Nothing
>>> orElse Nothing (Just 'a')
Just 'a'
>>> orElse (Just 'a') Nothing
Just 'a'
>>> orElse (Just 'a') (Just 'b')
Just 'a'

Since: 0.1.0.0

Function combinators on generic functions

recoverMp :: MonadPlus m => GenericM m -> GenericM m Source #

Recover from the failure of monadic transformation by identity

Since: 0.1.0.0

recoverQ :: MonadPlus m => r -> GenericQ (m r) -> GenericQ (m r) Source #

Recover from the failure of monadic query by a constant

Since: 0.1.0.0

choiceMp :: MonadPlus m => GenericM m -> GenericM m -> GenericM m Source #

Choice for monadic transformations

Since: 0.1.0.0

choiceQ :: MonadPlus m => GenericQ (m r) -> GenericQ (m r) -> GenericQ (m r) Source #

Choice for monadic queries

Since: 0.1.0.0

Type extension for unary type constructors

ext1 :: (Data a, Typeable t) => c a -> (forall d. Data d => c (t d)) -> c a Source #

Flexible type extension

Since: 0.3

ext1T :: (Data d, Typeable t) => (forall e. Data e => e -> e) -> (forall f. Data f => t f -> t f) -> d -> d Source #

Type extension of transformations for unary type constructors

Since: 0.1.0.0

ext1M :: (Monad m, Data d, Typeable t) => (forall e. Data e => e -> m e) -> (forall f. Data f => t f -> m (t f)) -> d -> m d Source #

Type extension of monadic transformations for type constructors

Since: 0.1.0.0

ext1Q :: (Data d, Typeable t) => (d -> q) -> (forall e. Data e => t e -> q) -> d -> q Source #

Type extension of queries for type constructors

Since: 0.1.0.0

ext1R :: (Monad m, Data d, Typeable t) => m d -> (forall e. Data e => m (t e)) -> m d Source #

Type extension of readers for type constructors

Since: 0.1.0.0

ext1B :: (Data a, Typeable t) => a -> (forall b. Data b => t b) -> a Source #

Type extension of builders for type constructors

Since: 0.2

Type extension for binary type constructors

ext2 :: (Data a, Typeable t) => c a -> (forall d1 d2. (Data d1, Data d2) => c (t d1 d2)) -> c a Source #

Flexible type extension

ext2T :: (Data d, Typeable t) => (forall e. Data e => e -> e) -> (forall d1 d2. (Data d1, Data d2) => t d1 d2 -> t d1 d2) -> d -> d Source #

Type extension of transformations for unary type constructors

Since: 0.3

ext2M :: (Monad m, Data d, Typeable t) => (forall e. Data e => e -> m e) -> (forall d1 d2. (Data d1, Data d2) => t d1 d2 -> m (t d1 d2)) -> d -> m d Source #

Type extension of monadic transformations for type constructors

Since: 0.3

ext2Q :: (Data d, Typeable t) => (d -> q) -> (forall d1 d2. (Data d1, Data d2) => t d1 d2 -> q) -> d -> q Source #

Type extension of queries for type constructors

Since: 0.3

ext2R :: (Monad m, Data d, Typeable t) => m d -> (forall d1 d2. (Data d1, Data d2) => m (t d1 d2)) -> m d Source #

Type extension of readers for type constructors

Since: 0.3

ext2B :: (Data a, Typeable t) => a -> (forall d1 d2. (Data d1, Data d2) => t d1 d2) -> a Source #

Type extension of builders for type constructors

Since: 0.3