#if defined(__GLASGOW_HASKELL__) && __GLASGOW_HASKELL__ >= 704
#define USE_DEFAULT_SIGNATURES
#endif
#ifdef USE_DEFAULT_SIGNATURES
#endif
module Text.Parser.Char
(
oneOf
, noneOf
, oneOfSet
, noneOfSet
, spaces
, space
, newline
, tab
, upper
, lower
, alphaNum
, letter
, digit
, hexDigit
, octDigit
, satisfyRange
, CharParsing(..)
) where
#if __GLASGOW_HASKELL__ < 710
import Control.Applicative
#endif
import Control.Monad.Trans.Class
import Control.Monad.Trans.State.Lazy as Lazy
import Control.Monad.Trans.State.Strict as Strict
import Control.Monad.Trans.Writer.Lazy as Lazy
import Control.Monad.Trans.Writer.Strict as Strict
import Control.Monad.Trans.RWS.Lazy as Lazy
import Control.Monad.Trans.RWS.Strict as Strict
import Control.Monad.Trans.Reader
import Control.Monad.Trans.Identity
import Control.Monad (MonadPlus(..))
import Data.Char
import Data.CharSet (CharSet(..))
import qualified Data.CharSet as CharSet
import Data.Foldable
import qualified Data.IntSet as IntSet
#if __GLASGOW_HASKELL__ < 710
import Data.Monoid
#endif
import Data.Text
import qualified Text.ParserCombinators.ReadP as ReadP
import qualified Text.Parsec as Parsec
import qualified Data.Attoparsec.Types as Att
import qualified Data.Attoparsec.Combinator as Att
import Text.Parser.Combinators
oneOf :: CharParsing m => [Char] -> m Char
oneOf xs = oneOfSet (CharSet.fromList xs)
noneOf :: CharParsing m => [Char] -> m Char
noneOf xs = noneOfSet (CharSet.fromList xs)
oneOfSet :: CharParsing m => CharSet -> m Char
oneOfSet (CharSet True _ is) = satisfy (\c -> IntSet.member (fromEnum c) is)
oneOfSet (CharSet False _ is) = satisfy (\c -> not (IntSet.member (fromEnum c) is))
noneOfSet :: CharParsing m => CharSet -> m Char
noneOfSet s = oneOfSet (CharSet.complement s)
spaces :: CharParsing m => m ()
spaces = skipMany space <?> "white space"
space :: CharParsing m => m Char
space = satisfy isSpace <?> "space"
newline :: CharParsing m => m Char
newline = char '\n' <?> "new-line"
tab :: CharParsing m => m Char
tab = char '\t' <?> "tab"
upper :: CharParsing m => m Char
upper = satisfy isUpper <?> "uppercase letter"
lower :: CharParsing m => m Char
lower = satisfy isLower <?> "lowercase letter"
alphaNum :: CharParsing m => m Char
alphaNum = satisfy isAlphaNum <?> "letter or digit"
letter :: CharParsing m => m Char
letter = satisfy isAlpha <?> "letter"
digit :: CharParsing m => m Char
digit = satisfy isDigit <?> "digit"
hexDigit :: CharParsing m => m Char
hexDigit = satisfy isHexDigit <?> "hexadecimal digit"
octDigit :: CharParsing m => m Char
octDigit = satisfy isOctDigit <?> "octal digit"
satisfyRange :: CharParsing m => Char -> Char -> m Char
satisfyRange a z = satisfy (\c -> c >= a && c <= z)
class Parsing m => CharParsing m where
satisfy :: (Char -> Bool) -> m Char
#ifdef USE_DEFAULT_SIGNATURES
default satisfy :: (MonadTrans t, CharParsing n, Monad n, m ~ t n) =>
(Char -> Bool) ->
m Char
satisfy = lift . satisfy
#endif
char :: Char -> m Char
char c = satisfy (c ==) <?> show [c]
notChar :: Char -> m Char
notChar c = satisfy (c /=)
anyChar :: m Char
anyChar = satisfy (const True)
string :: String -> m String
string s = s <$ try (traverse_ char s) <?> show s
text :: Text -> m Text
text t = t <$ string (unpack t)
instance (CharParsing m, MonadPlus m) => CharParsing (Lazy.StateT s m) where
satisfy = lift . satisfy
char = lift . char
notChar = lift . notChar
anyChar = lift anyChar
string = lift . string
text = lift . text
instance (CharParsing m, MonadPlus m) => CharParsing (Strict.StateT s m) where
satisfy = lift . satisfy
char = lift . char
notChar = lift . notChar
anyChar = lift anyChar
string = lift . string
text = lift . text
instance (CharParsing m, MonadPlus m) => CharParsing (ReaderT e m) where
satisfy = lift . satisfy
char = lift . char
notChar = lift . notChar
anyChar = lift anyChar
string = lift . string
text = lift . text
instance (CharParsing m, MonadPlus m, Monoid w) => CharParsing (Strict.WriterT w m) where
satisfy = lift . satisfy
char = lift . char
notChar = lift . notChar
anyChar = lift anyChar
string = lift . string
text = lift . text
instance (CharParsing m, MonadPlus m, Monoid w) => CharParsing (Lazy.WriterT w m) where
satisfy = lift . satisfy
char = lift . char
notChar = lift . notChar
anyChar = lift anyChar
string = lift . string
text = lift . text
instance (CharParsing m, MonadPlus m, Monoid w) => CharParsing (Lazy.RWST r w s m) where
satisfy = lift . satisfy
char = lift . char
notChar = lift . notChar
anyChar = lift anyChar
string = lift . string
text = lift . text
instance (CharParsing m, MonadPlus m, Monoid w) => CharParsing (Strict.RWST r w s m) where
satisfy = lift . satisfy
char = lift . char
notChar = lift . notChar
anyChar = lift anyChar
string = lift . string
text = lift . text
instance (CharParsing m, MonadPlus m) => CharParsing (IdentityT m) where
satisfy = lift . satisfy
char = lift . char
notChar = lift . notChar
anyChar = lift anyChar
string = lift . string
text = lift . text
instance Parsec.Stream s m Char => CharParsing (Parsec.ParsecT s u m) where
satisfy = Parsec.satisfy
char = Parsec.char
notChar c = Parsec.satisfy (/= c)
anyChar = Parsec.anyChar
string = Parsec.string
instance Att.Chunk t => CharParsing (Att.Parser t) where
satisfy p = fmap e2c $ Att.satisfyElem $ p . e2c
where e2c = Att.chunkElemToChar (undefined :: t)
instance CharParsing ReadP.ReadP where
satisfy = ReadP.satisfy
char = ReadP.char
notChar c = ReadP.satisfy (/= c)
anyChar = ReadP.get
string = ReadP.string