t-regex-0.1.0.0: Matchers and grammars using tree regular expressions

Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.MultiGenerics

Description

Multirec-style generics, indexed by data kind k. Pattern functors should have kind (k -> *) -> k -> *.

Synopsis

Documentation

newtype Fix f ix Source

Multirec-style fix-point, indexed by data kind.

Constructors

Fix 

Fields

unFix :: f (Fix f) ix
 

data family Sing a Source

The singleton kind-indexed data family. Taken from the singletons package.

Instances

Eq (Sing Ty a) 
data Sing Ty where 

class SingI a where Source

A SingI constraint is essentially an implicitly-passed singleton.

Methods

sing :: Sing a Source

Produce the singleton explicitly. You will likely need the ScopedTypeVariables extension to use this method the way you want.

Instances

class ShowM f where Source

Convert a pattern functor to a readable String.

Methods

showM :: f ix -> String Source

An index-independent way to show a value.

Instances

Show c => ShowM k (Wrap k c) 
ShowM Ty (Fix Ty Bis) 

class EqM f where Source

We have equality for each instantiation of the pattern functor.

Methods

eqM :: f ix -> f xi -> Bool Source

Instances

Eq c => EqM k (Wrap k c) 

type GenM f = forall ix. Sing ix -> Gen (f ix) Source

Generate a random element given a proxy.

class ArbitraryM f where Source

Methods

arbitraryM :: GenM f Source

Instances

class Generic1m f where Source

Representable types of kind * -> *. This class is derivable in GHC with the DeriveGeneric flag on.

Associated Types

type Rep1m f :: (k -> *) -> k -> * Source

Generic representation type.

Methods

from1k :: f a ix -> Rep1m f a ix Source

Convert from the datatype to its representation.

to1k :: Rep1m f a ix -> f a ix Source

Convert from the representation to the datatype.

Instances

Generic1m Ty Bis

Implementation of Generic1m for Bis. This is required to use tree regular expressions.

Generic1m k (Par1m k xi) 
Generic1m k (U1m (k -> *) k) 
Generic1m k (V1m (k -> *) k) 
Generic1m k f => Generic1m k (Tag1m k f xi) 
(Generic1m k f, Generic1m k g) => Generic1m k ((:++:) k f g) 
Generic1m k (Rec1m k f xi) 
(Generic1m k f, Generic1m k g) => Generic1m k ((:**:) (k -> *) k f g) 
Generic1m k (K1m k (k -> *) k i c) 

data V1m p ix Source

Void: used for datatypes without constructors.

Instances

Generic1m k (V1m (k -> *) k) 
type Rep1m k (V1m (k -> *) k) = V1m (k -> *) k 

data U1m p ix Source

Unit: used for constructors without arguments.

Constructors

U1m 

Instances

Generic1m k (U1m (k -> *) k) 
Eq (U1m k k p ix) 
Ord (U1m k k p ix) 
Read (U1m k k p ix) 
Show (U1m k k p ix) 
type Rep1m k (U1m (k -> *) k) = U1m (k -> *) k 

newtype Par1m xi p ix Source

Used for marking occurrences of the parameter.

Constructors

Par1m 

Fields

unPar1m :: p xi
 

Instances

Generic1m k (Par1m k xi) 
type Rep1m k (Par1m k xi) = Par1m k xi 

newtype Rec1m f xi p ix Source

Recursive calls of kind '* -> *'.

Constructors

Rec1m 

Fields

unRec1m :: f (p xi)
 

Instances

Generic1m k (Rec1m k f xi) 
type Rep1m k (Rec1m k f xi) = Rec1m k f xi 

newtype K1m i c p ix Source

Constants, additional parameters and recursion of kind *.

Constructors

K1m 

Fields

unK1m :: c
 

Instances

Generic1m k (K1m k (k -> *) k i c) 
Eq c => Eq (K1m k k k i c p ix) 
Ord c => Ord (K1m k k k i c p ix) 
Read c => Read (K1m k k k i c p ix) 
Show c => Show (K1m k k k i c p ix) 
type Rep1m k1 (K1m k (k1 -> *) k1 i c) = K1m k (k1 -> *) k1 i c 

data (f :++: g) p ix infixr 5 Source

Sums: encode choice between constructors.

Constructors

L1m (f p ix) 
R1m (g p ix) 

Instances

(Generic1m k f, Generic1m k g) => Generic1m k ((:++:) k f g) 
(Eq (f p ix), Eq (g p ix)) => Eq ((:++:) k f g p ix) 
(Ord (f p ix), Ord (g p ix)) => Ord ((:++:) k f g p ix) 
(Read (f p ix), Read (g p ix)) => Read ((:++:) k f g p ix) 
(Show (f p ix), Show (g p ix)) => Show ((:++:) k f g p ix) 
type Rep1m k ((:++:) k f g) = (:++:) k f g 

data (f :**: g) p ix infixr 6 Source

Products: encode multiple arguments to constructors.

Constructors

(f p ix) :**: (g p ix) infixr 6 

Instances

(Generic1m k f, Generic1m k g) => Generic1m k ((:**:) (k -> *) k f g) 
(Eq (f p ix), Eq (g p ix)) => Eq ((:**:) k k f g p ix) 
(Ord (f p ix), Ord (g p ix)) => Ord ((:**:) k k f g p ix) 
(Read (f p ix), Read (g p ix)) => Read ((:**:) k k f g p ix) 
(Show (f p ix), Show (g p ix)) => Show ((:**:) k k f g p ix) 
type Rep1m k ((:**:) (k -> *) k f g) = (:**:) (k -> *) k f g 

data Tag1m f xi p ix where Source

Tags: encode return type of a GADT constructor.

Constructors

Tag1m :: f p ix -> Tag1m f ix p ix 

Instances

Generic1m k f => Generic1m k (Tag1m k f xi) 
type Rep1m k (Tag1m k f xi) = Tag1m k f xi