| Safe Haskell | Safe-Inferred |
|---|---|
| Language | Haskell2010 |
Data.CharSet
Description
It is recommended to import this module qualified to avoid name conflicts with functions from the Prelude.
Enabling OverloadedStrings
will allow declaring CharSets using string literal syntax.
{-# LANGUAGE OverloadedStrings #-}
import qualified Data.CharSet as CS
vowels :: CS.CharSet
vowels = "aeiou"
Synopsis
- data CharSet
- singleton :: Char -> CharSet
- fromRange :: (Char, Char) -> CharSet
- fromList :: [Char] -> CharSet
- fromRanges :: [(Char, Char)] -> CharSet
- insert :: Char -> CharSet -> CharSet
- insertRange :: (Char, Char) -> CharSet -> CharSet
- delete :: Char -> CharSet -> CharSet
- deleteRange :: (Char, Char) -> CharSet -> CharSet
- map :: (Char -> Char) -> CharSet -> CharSet
- not :: CharSet -> CharSet
- union :: CharSet -> CharSet -> CharSet
- difference :: CharSet -> CharSet -> CharSet
- intersection :: CharSet -> CharSet -> CharSet
- member :: Char -> CharSet -> Bool
- notMember :: Char -> CharSet -> Bool
- elems :: CharSet -> [Char]
- ranges :: CharSet -> [(Char, Char)]
- empty :: CharSet
- digit :: CharSet
- word :: CharSet
- space :: CharSet
- ascii :: CharSet
- asciiAlpha :: CharSet
- asciiUpper :: CharSet
- asciiLower :: CharSet
- valid :: CharSet -> Bool
The CharSet type
A set of Chars.
The members are stored as contiguous ranges of Chars. This is efficient
when the members form contiguous ranges since many Chars can be represented
with just one range.
CharSet operations
Variables used:
- \(n\): the number of
Charranges - \(s\): the number of
Chars - \(C\): the maximum bits in a
Char, i.e. 21 - \(n\), \(m\): the number of
Charranges in the first and second sets respectively, for functions taking two sets
fromRanges :: [(Char, Char)] -> CharSet Source #
\(O(n \min(n,C))\). Create a set from the given Char ranges (inclusive).
insertRange :: (Char, Char) -> CharSet -> CharSet Source #
\(O(\min(n,C))\). Insert all Chars in a range (inclusive) into a set.
deleteRange :: (Char, Char) -> CharSet -> CharSet Source #
\(O(\min(n,C))\). Delete a Char range (inclusive) from a set.
map :: (Char -> Char) -> CharSet -> CharSet Source #
\(O(s \min(s,C))\). Map a function over all Chars in a set.
union :: CharSet -> CharSet -> CharSet Source #
\(O(m \min(n+m,C))\). The union of two sets.
Prefer strict left-associative unions, since this is a strict structure and the runtime is linear in the size of the second argument.
difference :: CharSet -> CharSet -> CharSet Source #
\(O(m \min(n+m,C))\). The difference of two sets.
intersection :: CharSet -> CharSet -> CharSet Source #
\(O(n + m \min(n+m,C))\). The intersection of two sets.
Available CharSets
Unicode space characters and the control characters
'\t','\n','\r','\f','\v'.
Agrees with isSpace.
asciiAlpha :: CharSet Source #
ASCII alphabet. 'A'..'Z','a'..'z'.
asciiUpper :: CharSet Source #
ASCII uppercase Chars. 'A'..'Z'. Agrees with
isAsciiUpper.
asciiLower :: CharSet Source #
ASCII lowercase Chars. 'a'..'z'. Agrees with
isAsciiLower.