Maintainer | hapytexeu+gh@gmail.com |
---|---|
Stability | experimental |
Portability | POSIX |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Data.Pattern.Any
Description
The module exposes two QuasiQuoter
s 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 QuasiQuoter
s, it is however required that the variables
have the same type in each pattern.
Synopsis
- anypat :: QuasiQuoter
- maypat :: QuasiQuoter
- rangepat :: QuasiQuoter
- hashpat :: QuasiQuoter
- ϵ :: QuasiQuoter
- combineHashViewPats :: NonEmpty Pat -> Q Pat
- patVars :: Pat -> [Name]
- patVars' :: Pat -> [Name] -> [Name]
- data RangeObj a = RangeObj {
- rangeBegin :: a
- rangeThen :: Maybe a
- rangeEnd :: Maybe a
- pattern FromRange :: a -> RangeObj a
- pattern FromThenRange :: a -> a -> RangeObj a
- pattern FromToRange :: a -> a -> RangeObj a
- pattern FromThenToRange :: a -> a -> a -> RangeObj a
- rangeToList :: Enum a => RangeObj a -> [a]
- inRange :: Enum a => RangeObj a -> a -> Bool
- (∈) :: Enum a => a -> RangeObj a -> Bool
- (∋) :: Enum a => RangeObj a -> a -> Bool
- rangeLength :: Enum a => RangeObj a -> Maybe Int
- rangeDirection :: Ord a => RangeObj a -> Ordering
- rangeLastValue :: Enum a => RangeObj a -> Maybe a
Quasiquoters
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
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
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`.
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
Arguments
:: NonEmpty Pat | The non-empty list of view patterns that are compiled into a viw pattern. |
-> Q Pat | A |
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
Arguments
:: Pat | The |
-> [Name] | The list of variable names that is used to collect (fragments) of the pattern. |
Provides a list of variable names for a given Pat
tern. 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.
Arguments
:: Pat | The |
-> [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 Pat
tern. 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
A RangeObj
that specifies a range with a start value and optionally a step value and end value.
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]
.
Arguments
:: Enum a | |
=> RangeObj a | The |
-> [a] | A list of items the |
Convert the RangeObj
to a list of the values defined by the range.
Arguments
:: Enum a | |
=> RangeObj a | The |
-> 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.
Arguments
:: Enum a | |
=> RangeObj a | The |
-> Maybe Int | The number of elements of the range object, given that can be determined easily; |
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).