-----------------------------------------------------------------------------
-- |
-- Module      :  Data.CharSet.Posix.Unicode
-- Copyright   :  (c) Edward Kmett 2010
-- License     :  BSD3
-- Maintainer  :  ekmett@gmail.com
-- Stability   :  experimental
-- Portability :  portable
--
-------------------------------------------------------------------------------

module Data.CharSet.Posix.Unicode
    ( posixUnicode
    , lookupPosixUnicodeCharSet
    -- * POSIX ASCII \"classes\"
    , alnum, alpha, ascii, blank, cntrl, digit, graph, print, word, punct, space, upper, lower, xdigit
    ) where

import Prelude hiding (print)
import Data.Char
import Data.CharSet
import qualified Data.CharSet.Unicode.Category as Category
import qualified Data.CharSet.Unicode.Block as Block
import Data.HashMap.Lazy (HashMap)
import qualified Data.HashMap.Lazy as HashMap

alnum, alpha, ascii, blank, cntrl, digit, graph, print, word, punct, space, upper, lower, xdigit :: CharSet
alnum :: CharSet
alnum = CharSet
alpha CharSet -> CharSet -> CharSet
`union` CharSet
digit
ascii :: CharSet
ascii = CharSet
Block.basicLatin
alpha :: CharSet
alpha = CharSet
Category.letterAnd
blank :: CharSet
blank = Char -> CharSet -> CharSet
insert Char
'\t' CharSet
Category.space
cntrl :: CharSet
cntrl = CharSet
Category.control
digit :: CharSet
digit = CharSet
Category.decimalNumber
lower :: CharSet
lower = CharSet
Category.lowercaseLetter
upper :: CharSet
upper = CharSet
Category.uppercaseLetter
graph :: CharSet
graph = CharSet -> CharSet
complement (CharSet
Category.separator CharSet -> CharSet -> CharSet
`union` CharSet
Category.other)
print :: CharSet
print = CharSet -> CharSet
complement (CharSet
Category.other)
word :: CharSet
word  = CharSet
Category.letter CharSet -> CharSet -> CharSet
`union` CharSet
Category.number CharSet -> CharSet -> CharSet
`union` CharSet
Category.connectorPunctuation
punct :: CharSet
punct = CharSet
Category.punctuation CharSet -> CharSet -> CharSet
`union` CharSet
Category.symbol
space :: CharSet
space = String -> CharSet
fromList String
" \t\r\n\v\f" CharSet -> CharSet -> CharSet
`union` CharSet
Category.separator
xdigit :: CharSet
xdigit = CharSet
digit CharSet -> CharSet -> CharSet
`union` Char -> Char -> CharSet
range Char
'a' Char
'f' CharSet -> CharSet -> CharSet
`union` Char -> Char -> CharSet
range Char
'A' Char
'F'

-- :digit:, etc.
posixUnicode :: HashMap String CharSet
posixUnicode :: HashMap String CharSet
posixUnicode = forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
    [ (String
"alnum", CharSet
alnum)
    , (String
"alpha", CharSet
alpha)
    , (String
"ascii", CharSet
ascii)
    , (String
"blank", CharSet
blank)
    , (String
"cntrl", CharSet
cntrl)
    , (String
"digit", CharSet
digit)
    , (String
"graph", CharSet
graph)
    , (String
"print", CharSet
print)
    , (String
"word",  CharSet
word)
    , (String
"punct", CharSet
punct)
    , (String
"space", CharSet
space)
    , (String
"upper", CharSet
upper)
    , (String
"lower", CharSet
lower)
    , (String
"xdigit", CharSet
xdigit)
    ]

lookupPosixUnicodeCharSet :: String -> Maybe CharSet
lookupPosixUnicodeCharSet :: String -> Maybe CharSet
lookupPosixUnicodeCharSet String
s = forall k v. (Eq k, Hashable k) => k -> HashMap k v -> Maybe v
HashMap.lookup (forall a b. (a -> b) -> [a] -> [b]
Prelude.map Char -> Char
toLower String
s) HashMap String CharSet
posixUnicode