first-class-patterns-0.3.2.4: First class patterns and pattern matching, using type families

LicenseBSD3
MaintainerBrent Yorgey <byorgey@cis.upenn.edu>
Stabilityexperimental
Portabilitynon-portable (see .cabal)
Safe HaskellNone
LanguageHaskell2010

Data.Pattern.Common

Contents

Description

A collection of useful pattern combinators.

Synopsis

Pattern combinators

Basic patterns

var :: Pattern '[a] a Source #

Variable pattern: always succeeds, and binds the value to a variable.

give :: b -> Pattern '[b] a Source #

give b always succeeds, ignoring the matched value and providing the value b instead. Useful in conjunction with (/\) for providing default values in cases that would otherwise not bind any values.

__ :: Pattern '[] a Source #

Wildcard pattern: always succeeds, binding no variables. (This is written as two underscores.)

pfail :: Pattern '[] a Source #

Failure pattern: never succeeds.

cst :: Eq a => a -> Pattern '[] a Source #

Constant pattern: test for equality to the given constant.

cst x = is (==x).

(/\) :: Pattern vs1 a -> Pattern vs2 a -> Pattern (vs1 :++: vs2) a Source #

Conjunctive (and) pattern: matches a value against two patterns, and succeeds only if both succeed, binding variables from both.

(/\) = mk2 (\a -> Just (a,a))

(\/) :: Pattern as a -> Pattern as a -> Pattern as a Source #

Disjunctive (or) pattern: matches a value against the first pattern, or against the second pattern if the first one fails.

view :: (a -> b) -> Pattern vs b -> Pattern vs a Source #

View pattern: do some computation, then pattern match on the result.

(-->) :: (a -> b) -> Pattern vs b -> Pattern vs a infix 5 Source #

Convenient infix synonym for view.

tryView :: (a -> Maybe b) -> Pattern vs b -> Pattern vs a Source #

Partial view pattern: do some (possibly failing) computation, then pattern match on the result if the computation is successful.

(-?>) :: (a -> Maybe b) -> Pattern vs b -> Pattern vs a infix 5 Source #

Convenient infix synonym for tryView.

is :: (a -> Bool) -> Pattern '[] a Source #

Predicate pattern. Succeeds if the given predicate yields True, fails otherwise.

Can be used with (/\) for some uses similar to pattern guards:

match a $
     left (var /\ is even) ->> id
 <|> left  __              ->> const 0
 <|> right __              ->> const 1

Note that is is like mk0 but with Bool instead of Maybe ().

Computational patterns

pfilter :: (Distribute vs, Foldable t) => Pattern vs a -> Pattern (Map [] vs) (t a) Source #

pfilter p matches every element of a Foldable data structure against the pattern p, discarding elements that do not match. From the matching elements, binds a list of values corresponding to each pattern variable.

pmap :: (Distribute vs, Traversable t) => Pattern vs a -> Pattern (Map t vs) (t a) Source #

pmap p matches every element of a Traversable data structure against the pattern p. The entire match fails if any of the elements fail to match p. If all the elements match, binds a t-structure full of bound values corresponding to each variable bound in p.

pfoldr :: (Foldable t, Functor t) => Pattern vs a -> Fun vs (b -> b) -> b -> Pattern '[b] (t a) Source #

pfoldr p f b matches every element of a Foldable data structure against the pattern p, discarding elements that do not match. Folds over the bindings produced by the matching elements to produce a summary value.

The same functionality could be achieved by matching with pfilter p and then appropriately combining and folding the resulting lists of bound values. In particular, if p binds only one value we have

match t (pfoldr p f b ->> id) === match t (pfilter p ->> foldr f b)

However, when p binds more than one value, it can be convenient to be able to process the bindings from each match together, rather than having to deal with them once they are separated out into separate lists.

Running matches

match :: a -> Clause a r -> r Source #

match satisfies the identity match a c = fromJust (tryMatch a c).

tryMatch :: a -> Clause a r -> Maybe r Source #

"Runs" a Clause, by matching it against a value and returning a result if it matches, or Nothing if the match fails.

mmatch :: Monad m => m a -> Clause a (m b) -> m b Source #

mmatch m p = m >>= elim p

Useful for applicative-looking monadic pattern matching, as in

ex7 :: IO ()
ex7 = mmatch getLine $
      cst "" ->> return ()
  <|> var    ->> putStrLn . ("You said " ++)

elim :: Clause a r -> a -> r Source #

elim = flip match

Useful for anonymous matching (or for building "eliminators", like maybe and either). For example:

either withLeft withRight = elim $
             left  var ->> withLeft
         <|> right var ->> withRight

Patterns for common data types

Booleans

true :: Pattern '[] Bool Source #

Match True.

false :: Pattern '[] Bool Source #

Match False.

Tuples

If you need to pattern match on tuples bigger than 5-tuples, you are Doing It Wrong.

unit :: Pattern '[] () Source #

A strict match on the unit value ().

tup0 :: Pattern '[] () Source #

A synonym for unit.

pair :: Pattern vs1 a -> Pattern vs2 b -> Pattern (vs1 :++: vs2) (a, b) Source #

Construct a pattern match against a pair from a pair of patterns.

tup2 :: Pattern vs1 a -> Pattern vs2 b -> Pattern (vs1 :++: vs2) (a, b) Source #

A synonym for pair.

tup3 :: Pattern vs1 a -> Pattern vs2 b -> Pattern vs3 c -> Pattern (vs1 :++: (vs2 :++: vs3)) (a, b, c) Source #

Match a 3-tuple.

tup4 :: Pattern vs1 a -> Pattern vs2 b -> Pattern vs3 c -> Pattern vs4 d -> Pattern (vs1 :++: (vs2 :++: (vs3 :++: vs4))) (a, b, c, d) Source #

Match a 4-tuple.

tup5 :: Pattern vs1 a -> Pattern vs2 b -> Pattern vs3 c -> Pattern vs4 d -> Pattern vs5 e -> Pattern (vs1 :++: (vs2 :++: (vs3 :++: (vs4 :++: vs5)))) (a, b, c, d, e) Source #

Match a 5-tuple.

Maybe

nothing :: Pattern '[] (Maybe a) Source #

Match the Nothing constructor of Maybe.

just :: Pattern vs a -> Pattern vs (Maybe a) Source #

Match the Just constructor of Maybe.

Either

left :: Pattern vs a -> Pattern vs (Either a b) Source #

Match the Left constructor of Either.

right :: Pattern vs b -> Pattern vs (Either a b) Source #

Match the Right constructor of Either.

Lists

nil :: Pattern '[] [a] Source #

Match the empty list.

cons :: Pattern vs1 a -> Pattern vs2 [a] -> Pattern (vs1 :++: vs2) [a] Source #

Match a cons.

Numerics

zero :: (Integral a, Eq a) => Pattern '[] a Source #

Match zero.

suc :: (Integral a, Eq a) => Pattern vs a -> Pattern vs a Source #

Match a natural number which is the successor of another natural (and match the predecessor with a nested pattern). Together, zero and suc allow viewing Integral types as Peano numbers.

Note that suc never matches negative numbers.

Building your own patterns

Smart constructors for patterns

Build patterns from a selector function.

mk0 :: (a -> Maybe ()) -> Pattern '[] a Source #

mk1 :: (a -> Maybe b) -> Pattern vs b -> Pattern vs a Source #

mk2 :: (a -> Maybe (b, c)) -> Pattern vs1 b -> Pattern vs2 c -> Pattern (vs1 :++: vs2) a Source #

mk3 :: (a -> Maybe (b, c, d)) -> Pattern vs1 b -> Pattern vs2 c -> Pattern vs3 d -> Pattern (vs1 :++: (vs2 :++: vs3)) a Source #

mk4 :: (a -> Maybe (b, c, d, e)) -> Pattern vs1 b -> Pattern vs2 c -> Pattern vs3 d -> Pattern vs4 e -> Pattern (vs1 :++: (vs2 :++: (vs3 :++: vs4))) a Source #

mk5 :: (a -> Maybe (b, c, d, e, f)) -> Pattern vs1 b -> Pattern vs2 c -> Pattern vs3 d -> Pattern vs4 e -> Pattern vs5 f -> Pattern (vs1 :++: (vs2 :++: (vs3 :++: (vs4 :++: vs5)))) a Source #