{-# LANGUAGE FlexibleContexts #-} ----------------------------------------------------------------------------- -- | -- Module : Text.ParserCombinators.Parsely.Char -- Copyright : (c) Daan Leijen 1999-2001, (c) Samuel Bronson 2007 -- License : BSD-style -- -- Maintainer : naesten@gmail.com -- Stability : provisional -- Portability : non-portable (multi-param classes, functional dependencies) -- -- Commonly used character parsers. -- ----------------------------------------------------------------------------- module Text.ParserCombinators.Parsely.Char ( spaces, space , newline, tab , upper, lower, alphaNum, letter , digit, hexDigit, octDigit , char, string , anyChar, oneOf, noneOf , satisfy ) where import Prelude import Data.Char import Text.ParserCombinators.Parsec.Pos(SourcePos, updatePosChar, updatePosString) import Text.ParserCombinators.Parsely.Class ----------------------------------------------------------- -- Character parsers ----------------------------------------------------------- oneOf, noneOf :: MonadParsec m Char SourcePos => [Char] -> m Char oneOf cs = satisfy (\c -> elem c cs) noneOf cs = satisfy (\c -> not (elem c cs)) spaces :: MonadParsec m Char SourcePos => m () spaces = skipMany space "white space" space, newline, tab :: MonadParsec m Char SourcePos => m Char space = satisfy (isSpace) "space" newline = char '\n' "new-line" tab = char '\t' "tab" upper, lower, alphaNum, letter, digit, hexDigit, octDigit :: MonadParsec m Char SourcePos => m Char upper = satisfy (isUpper) "uppercase letter" lower = satisfy (isLower) "lowercase letter" alphaNum = satisfy (isAlphaNum) "letter or digit" letter = satisfy (isAlpha) "letter" digit = satisfy (isDigit) "digit" hexDigit = satisfy (isHexDigit) "hexadecimal digit" octDigit = satisfy (isOctDigit) "octal digit" char :: MonadParsec m Char SourcePos => Char -> m Char char c = satisfy (==c) show [c] anyChar :: MonadParsec m Char SourcePos => m Char anyChar = satisfy (const True) ----------------------------------------------------------- -- Primitive character parsers ----------------------------------------------------------- satisfy :: MonadParsec m Char SourcePos => (Char -> Bool) -> m Char satisfy f = tokenPrim (\c -> show [c]) (\pos c cs -> updatePosChar pos c) (\c -> if f c then Just c else Nothing) string :: MonadParsec m Char SourcePos => String -> m String string s = tokens show updatePosString s