is-0.2: Pattern predicates using TH

Safe HaskellNone
LanguageHaskell2010

Data.Generics.Is

Contents

Description

Generate predicates from constructor names or from quoted patterns.

You must enable the TemplateHaskell extension to use this module.

Synopsis

From constructors

Given a constructor (or pattern synonym) for type T, is generates a function of type T → Bool.

The function evaluates its argument to WHNF, and returns True if the head constructor matches the given one, False otherwise.

$(isNot 'Con) ≡ not . $(is 'Con)
>>> $(is 'Just) (Just 5)
True
>>> $(isNot '(:)) [1,2,3]
False

From patterns

Given a pattern for type T, isP generates a function of type T → Bool.

The function returns True if the expression matches the pattern; a and False otherwise.

$(isNot patQ) ≡ not . $(isP patQ)
$(isP [p| Con{} |]) ≡ $(is 'Con)
>>> $(isP [p| Just _ |]) Nothing
False
>>> $(isNotP [_,_,_]) [2,1]
True

Predicate declarations

Given a type T, for each constructor C, we can declare predicates isC, isNotC : T → Bool.

Type T can be a newtype, data, or GADT declaration.

Constructors with non-alphanumeric names (e.g. :+:) are ignored silently. As a workaround, we suggest giving the constructors alphanumeric names, and creating pattern synonyms with the desired symbolic names.

data E a where
   Plus     :: E Int -> E Int -> E Int
   And      :: E Bool -> E Bool -> E Bool 
   Lit      :: a -> E a
   (:*:)    :: (Num a) => E a -> E a -> E a
   Showable :: (Show a) => a -> E String

pattern a :+: b = Plus a b

makePredicates :: Name -> Q [Dec] Source

Generate predicates of the form isC

>>> $(makePredicates ''T)
>>> isPlus (Plus (Lit 1) (Lit 2))
True

makePredicatesNot :: Name -> Q [Dec] Source

Generate predicates of the form isNotC

>>> $(makePredicatesNot ''T)
>>> isNotAnd (Showable True)
True

makePredicatesAll :: Name -> Q [Dec] Source

Generate predicates of both forms, isC and isNotC

$(makePredicatesAll ''T) ≡ $(makePredicates ''T) ; $(makePredicatesNot ''T)