parameterized-utils-1.0.0: Classes and data structures for working with data-kind indexed types

Copyright(c) Galois Inc 2013-2014
MaintainerJoe Hendrix <jhendrix@galois.com>
Safe HaskellNone
LanguageHaskell98

Data.Parameterized.TH.GADT

Contents

Description

This module declares template Haskell primitives so that it is easier to work with GADTs that have many constructors.

Synopsis

Documentation

structuralEquality :: TypeQ -> [(TypePat, ExpQ)] -> ExpQ Source #

declareStructuralEquality declares a structural equality predicate.

structuralTypeEquality :: TypeQ -> [(TypePat, ExpQ)] -> ExpQ Source #

structuralTypeEquality f returns a function with the type: forall x y . f x -> f y -> Maybe (x :~: y)

structuralTypeOrd Source #

Arguments

:: TypeQ 
-> [(TypePat, ExpQ)]

List of type patterns to match.

-> ExpQ 

structuralTypeEquality f returns a function with the type: forall x y . f x -> f y -> OrderingF x y

This implementation avoids matching on both the first and second parameters in a simple case expression in order to avoid stressing GHC's coverage checker. In the case that the first and second parameters have unique constructors, a simple numeric comparison is done to compute the result.

structuralTraversal :: TypeQ -> [(TypePat, ExpQ)] -> ExpQ Source #

structuralTraversal tp generates a function that applies a traversal f to the subterms with free variables in tp.

structuralShowsPrec :: TypeQ -> ExpQ Source #

structuralShow tp generates a function with the type tp -> ShowS that shows the constructor.

structuralHash :: TypeQ -> ExpQ Source #

structuralHash tp generates a function with the type Int -> tp -> Int that hashes type.

class PolyEq u v where Source #

A polymorphic equality operator that generalizes TestEquality.

Minimal complete definition

polyEqF

Methods

polyEqF :: u -> v -> Maybe (u :~: v) Source #

polyEq :: u -> v -> Bool Source #

Instances

PolyEq (NatRepr m) (NatRepr n) Source # 

Methods

polyEqF :: NatRepr m -> NatRepr n -> Maybe ((* :~: NatRepr m) (NatRepr n)) Source #

polyEq :: NatRepr m -> NatRepr n -> Bool Source #

TestEquality k f => PolyEq (Assignment k f x) (Assignment k f y) Source # 

Methods

polyEqF :: Assignment k f x -> Assignment k f y -> Maybe ((* :~: Assignment k f x) (Assignment k f y)) Source #

polyEq :: Assignment k f x -> Assignment k f y -> Bool Source #

Template haskell utilities that may be useful in other contexts.

conPat Source #

Arguments

:: ConstructorInfo

constructor information

-> String

generated name prefix

-> Q (Pat, [Name])

pattern and bound names

Given a constructor and string, this generates a pattern for matching the expression, and the names of variables bound by pattern in order they appear in constructor.

data TypePat Source #

Constructors

TypeApp TypePat TypePat

The application of a type.

AnyType

Match any type.

DataArg Int

Match the ith argument of the data type we are traversing.

ConType TypeQ

Match a ground type.

assocTypePats :: [Type] -> [(TypePat, v)] -> Type -> Q (Maybe v) Source #

Find value associated with first pattern that matches given pat if any.