any-pat-0.4.0.0: Quasiquoters that act on a sequence of patterns and compiles these view into patterns and expressions.
Maintainerhapytexeu+gh@gmail.com
Stabilityexperimental
PortabilityPOSIX
Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.Pattern.Any

Description

The module exposes two QuasiQuoters named anypat and maypat that allow compiling separate patterns into a single (view) pattern that will fire in case any of the patterns matches. If there are any variable names, it will match these. For the anypat it requires that all variables occur in all patterns. For maypat that is not a requirement. For both QuasiQuoters, it is however required that the variables have the same type in each pattern.

Synopsis

Quasiquoters

anypat Source #

Arguments

:: QuasiQuoter

The quasiquoter that can be used as expression and pattern.

A quasquoter to specify multiple patterns that will succeed if any of the patterns match. All patterns should have the same set of variables and these should have the same type, otherwise a variable would have two different types, and if a variable is absent in one of the patterns, the question is what to pass as value.

Examples:

{-# LANGUAGE ViewPatterns, QuasiQuotes #-}

example :: (Bool, a, a) -> a
example [anypat|(False, a, _), (True, _, a)|] = a

maypat Source #

Arguments

:: QuasiQuoter

The quasiquoter that can be used as expression and pattern.

A quasiquoter to specify multiple patterns that will succeed if any of these patterns match. Patterns don't have to have the same variable names but if a variable is shared over the different patterns, it should have the same type. In case a variable name does not appear in all patterns, it will be passed as a Maybe to the clause with Nothing if a pattern matched without that variable name, and a Just if the (first) pattern that matched had such variable.

Examples:

{-# LANGUAGE ViewPatterns, QuasiQuotes #-}

example :: (Bool, a) -> Maybe a
example [maypat|(True, a), _|] = a

rangepat Source #

Arguments

:: QuasiQuoter

The quasiquoter that can be used as expression and pattern.

A QuasiQuoter to parse a range expression to a RangeObj. In case the QuasiQuoter is used for a pattern, it compiles into a view pattern that will work if the element is a member of the RangeObj.

Examples:

{-# LANGUAGE ViewPatterns, QuasiQuotes #-}

positiveEven :: Int -> Bool
positiveEven [rangepat|0, 2 ..|] = True
positiveEven _ = False

hashpat :: QuasiQuoter Source #

A quasiquoter to make HashMap lookups more convenient. This can only be used as a pattern. It takes a sequence of view patterns, where it will perform the lookup on the expression part of the view pattern, and match the successful lookup with the pattern. The Just part is thus not used in the pattern part to indicate a successful lookup. If a single variable is used, it will make a lookup with a string literal with the same variable.

Examples:

{-# LANGUAGE ViewPatterns, QuasiQuotes #-}

sumab :: HashMap String Int -> Int
sumab [rangepat|"a" -> a, "b" -> b|] = a + b
sumab _ = 0

This will sum up the values for `"a"` and `"b"` in the HashMap, given these both exist. Otherwise, it returns `0`.

{-# LANGUAGE ViewPatterns, QuasiQuotes #-}

sumab :: HashMap String Int -> Int
sumab [rangepat|a, b|] = a + b
sumab _ = 0

This will sum up the values for `"a"` and `"b"` in the HashMap, given these both exist. Otherwise, it returns `0`.

ϵ Source #

Arguments

:: QuasiQuoter

The quasiquoter that can be used as expression and pattern.

An alias of the rangepat QuasiQuoter, this is used since it looks quite similar to ∊ [a .. b], beware that the ϵ in [ϵ|a .. b|] is not an element of character, but the Greek lunate epsilon character which only looks similar. The reason we use an epsiolon is because this can be used as an identifier, whereas the element of is an operator.

Examples:

{-# LANGUAGE ViewPatterns, QuasiQuotes #-}

positiveEven :: Int -> Bool
positiveEven [ϵ|2, 4 ..|] = True
positiveEven _ = False

compile hash patterns

combineHashViewPats Source #

Arguments

:: NonEmpty Pat

The non-empty list of view patterns that are compiled into a viw pattern.

-> Q Pat

A Pat that is a view pattern that will map a HashMap to make lookups and matches these with the given patterns.

Create a view pattern that maps a HashMap with a locally scoped hm parameter to a the patterns. It thus basically implicitly adds lookup to all expressions and matches these with the given patterns. The compilation fails if not all elements are view patterns.

derive variable names names from patterns

patVars Source #

Arguments

:: Pat

The Pattern to inspect.

-> [Name]

The list of variable names that is used to collect (fragments) of the pattern.

Provides a list of variable names for a given Pattern. The list is not sorted. If the same variable name occurs multiple times (which does not make much sense), it will be listed multiple times.

patVars' Source #

Arguments

:: Pat

The Pattern to inspect.

-> [Name]

The list of remaining elements that is added as tail.

-> [Name]

The list of variable names that is used to collect (fragments) of the pattern.

Provides a list of variable names for a given Pattern. The list is not sorted. If the same variable name occurs multiple times (which does not make much sense), it will be listed multiple times.

Range objects

data RangeObj a Source #

A RangeObj that specifies a range with a start value and optionally a step value and end value.

Constructors

RangeObj 

Fields

Instances

Instances details
Functor RangeObj Source # 
Instance details

Defined in Data.Pattern.Any

Methods

fmap :: (a -> b) -> RangeObj a -> RangeObj b #

(<$) :: a -> RangeObj b -> RangeObj a #

Read a => Read (RangeObj a) Source # 
Instance details

Defined in Data.Pattern.Any

Show a => Show (RangeObj a) Source # 
Instance details

Defined in Data.Pattern.Any

Methods

showsPrec :: Int -> RangeObj a -> ShowS #

show :: RangeObj a -> String #

showList :: [RangeObj a] -> ShowS #

Eq a => Eq (RangeObj a) Source # 
Instance details

Defined in Data.Pattern.Any

Methods

(==) :: RangeObj a -> RangeObj a -> Bool #

(/=) :: RangeObj a -> RangeObj a -> Bool #

pattern FromRange :: a -> RangeObj a Source #

A RangeObj object that only has a start value, in Haskell specified as [b ..].

pattern FromThenRange :: a -> a -> RangeObj a Source #

A RangeObj object that has a start value and end value, in Haskell specified as [b .. e].

pattern FromToRange :: a -> a -> RangeObj a Source #

A RangeObj object with a start and next value, in Haskell specified as [b, s ..].

pattern FromThenToRange :: a -> a -> a -> RangeObj a Source #

A RangeObj object with a start, next value and end value, in Haskell specified as [b, s .. e].

rangeToList Source #

Arguments

:: Enum a 
=> RangeObj a

The RangeObj item to convert to a list.

-> [a]

A list of items the RangeObj spans.

Convert the RangeObj to a list of the values defined by the range.

inRange Source #

Arguments

:: Enum a 
=> RangeObj a

The RangeObj for which we check membership.

-> a

The element for which we check the membership.

-> Bool 

Check if the given value is in the given RangeObj. This function has some caveats, especially with floating points or other Enum instances where fromEnum and toEnum are no bijections. For example for floating points, `12.5` and `12.2` both map on the same item, as a result, the enum will fail to work properly.

(∈) Source #

Arguments

:: Enum a 
=> a

The given element to check membership for.

-> RangeObj a

The RangeObj object for which we check membership.

-> Bool

True if the given element is an element of the given RangeObj object; False otherwise.

Flipped alias of inRange that checks if an element is in range of a given RangeObj.

(∋) Source #

Arguments

:: Enum a 
=> RangeObj a

The RangeObj object for which we check membership.

-> a

The given element to check membership for.

-> Bool

True if the given element is an element of the given RangeObj object; False otherwise.

Alias of inRange that checks if an element is in range of a given RangeObj.

rangeLength Source #

Arguments

:: Enum a 
=> RangeObj a

The RangeObj to determine the number of elements from.

-> Maybe Int

The number of elements of the range object, given that can be determined easily; Nothing otherwise.

Determine the number of items for a RangeObj, given that can be determined easily. This is only for ranges that have an end and where the next item is different from the previous (otherwise this generates an endless list).

rangeDirection Source #

Arguments

:: Ord a 
=> RangeObj a

The RangeObj to determine the direction.

-> Ordering

The direction of the RangeObj as an Ordering object.

Determine the direction of the range through an Ordering object. For an increasing sequence, LT is used, for a sequence that repeats the element, Eq is returned, and for a descreasing sequence GT is used.

rangeLastValue :: Enum a => RangeObj a -> Maybe a Source #

Determine the last value of a RangeObj, given the RangeObj has an explicit end value. The last value is not per se the end value. For example for [0, 3 .. 10], the last value will be 9. If the RangeObj is empty, or has no (explicit) end value, Nothing is returned.