parser-regex-0.1.0.0: Regex based parsers
Safe HaskellSafe-Inferred
LanguageHaskell2010

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

The CharSet type

data CharSet Source #

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.

Instances

Instances details
IsString CharSet Source #
fromString = fromList
Instance details

Defined in Regex.Internal.CharSet

Methods

fromString :: String -> CharSet #

Monoid CharSet Source #
mempty = empty
Instance details

Defined in Regex.Internal.CharSet

Semigroup CharSet Source #
(<>) = union
Instance details

Defined in Regex.Internal.CharSet

Show CharSet Source # 
Instance details

Defined in Regex.Internal.CharSet

Eq CharSet Source # 
Instance details

Defined in Regex.Internal.CharSet

Methods

(==) :: CharSet -> CharSet -> Bool #

(/=) :: CharSet -> CharSet -> Bool #

CharSet operations

Variables used:

  • \(n\): the number of Char ranges
  • \(s\): the number of Chars
  • \(C\): the maximum bits in a Char, i.e. 21
  • \(n\), \(m\): the number of Char ranges in the first and second sets respectively, for functions taking two sets

singleton :: Char -> CharSet Source #

\(O(1)\). A set of one Char.

fromRange :: (Char, Char) -> CharSet Source #

\(O(1)\). A Char range (inclusive).

fromList :: [Char] -> CharSet Source #

\(O(s \min(s,C))\). Create a set from Chars in a list.

fromRanges :: [(Char, Char)] -> CharSet Source #

\(O(n \min(n,C))\). Create a set from the given Char ranges (inclusive).

insert :: Char -> CharSet -> CharSet Source #

\(O(\min(n,C))\). Insert a Char into a set.

insertRange :: (Char, Char) -> CharSet -> CharSet Source #

\(O(\min(n,C))\). Insert all Chars in a range (inclusive) into a set.

delete :: Char -> CharSet -> CharSet Source #

\(O(\min(n,C))\). Delete a Char from 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.

not :: CharSet -> CharSet Source #

\(O(n)\). The complement of 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.

member :: Char -> CharSet -> Bool Source #

\(O(\min(n,C))\). Whether a Char is in a set.

notMember :: Char -> CharSet -> Bool Source #

\(O(\min(n,C))\). Whether a Char is not in a set.

elems :: CharSet -> [Char] Source #

\(O(s)\). The Chars in a set.

ranges :: CharSet -> [(Char, Char)] Source #

\(O(n)\). The contiguous ranges of Chars in a set.

Available CharSets

empty :: CharSet Source #

The empty set.

digit :: CharSet Source #

ASCII digits. '0'..'9'. Agrees with isDigit.

word :: CharSet Source #

ASCII alphabet, digits and underscore. 'A'..'Z','a'..'z','0'..'9','_'.

space :: CharSet Source #

Unicode space characters and the control characters '\t','\n','\r','\f','\v'. Agrees with isSpace.

ascii :: CharSet Source #

ASCII Chars. '\0'..'\127'. Agrees with isAscii.

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.

Testing

valid :: CharSet -> Bool Source #

Is the internal structure of the set valid?