{-# LANGUAGE GADTs #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# OPTIONS_GHC -fspec-constr -fspec-constr-count=8 #-}
module Distribution.Compat.CharParsing
(
oneOf
, noneOf
, spaces
, space
, newline
, tab
, upper
, lower
, alphaNum
, letter
, digit
, hexDigit
, octDigit
, satisfyRange
, CharParsing(..)
, integral
, munch1
, munch
, skipSpaces1
, module Distribution.Compat.Parsing
) where
import Prelude ()
import Distribution.Compat.Prelude
import Control.Monad.Trans.Class (lift)
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 (ReaderT (..))
import Control.Monad.Trans.Identity (IdentityT (..))
import Data.Char
import Data.Text (Text, unpack)
import qualified Text.Parsec as Parsec
import qualified Distribution.Compat.ReadP as ReadP
import Distribution.Compat.Parsing
oneOf :: CharParsing m => [Char] -> m Char
oneOf xs = satisfy (\c -> c `elem` xs)
{-# INLINE oneOf #-}
noneOf :: CharParsing m => [Char] -> m Char
noneOf xs = satisfy (\c -> c `notElem` xs)
{-# INLINE noneOf #-}
spaces :: CharParsing m => m ()
spaces = skipMany space <?> "white space"
{-# INLINE spaces #-}
space :: CharParsing m => m Char
space = satisfy isSpace <?> "space"
{-# INLINE space #-}
newline :: CharParsing m => m Char
newline = char '\n' <?> "new-line"
{-# INLINE newline #-}
tab :: CharParsing m => m Char
tab = char '\t' <?> "tab"
{-# INLINE tab #-}
upper :: CharParsing m => m Char
upper = satisfy isUpper <?> "uppercase letter"
{-# INLINE upper #-}
lower :: CharParsing m => m Char
lower = satisfy isLower <?> "lowercase letter"
{-# INLINE lower #-}
alphaNum :: CharParsing m => m Char
alphaNum = satisfy isAlphaNum <?> "letter or digit"
{-# INLINE alphaNum #-}
letter :: CharParsing m => m Char
letter = satisfy isAlpha <?> "letter"
{-# INLINE letter #-}
digit :: CharParsing m => m Char
digit = satisfy isDigit <?> "digit"
{-# INLINE digit #-}
hexDigit :: CharParsing m => m Char
hexDigit = satisfy isHexDigit <?> "hexadecimal digit"
{-# INLINE hexDigit #-}
octDigit :: CharParsing m => m Char
octDigit = satisfy isOctDigit <?> "octal digit"
{-# INLINE octDigit #-}
satisfyRange :: CharParsing m => Char -> Char -> m Char
satisfyRange a z = satisfy (\c -> c >= a && c <= z)
{-# INLINE satisfyRange #-}
class Parsing m => CharParsing m where
satisfy :: (Char -> Bool) -> m Char
char :: Char -> m Char
char c = satisfy (c ==) <?> show [c]
{-# INLINE char #-}
notChar :: Char -> m Char
notChar c = satisfy (c /=)
{-# INLINE notChar #-}
anyChar :: m Char
anyChar = satisfy (const True)
{-# INLINE anyChar #-}
string :: String -> m String
string s = s <$ try (traverse_ char s) <?> show s
{-# INLINE string #-}
text :: Text -> m Text
text t = t <$ string (unpack t)
{-# INLINE text #-}
instance (CharParsing m, MonadPlus m) => CharParsing (Lazy.StateT s m) where
satisfy = lift . satisfy
{-# INLINE satisfy #-}
char = lift . char
{-# INLINE char #-}
notChar = lift . notChar
{-# INLINE notChar #-}
anyChar = lift anyChar
{-# INLINE anyChar #-}
string = lift . string
{-# INLINE string #-}
text = lift . text
{-# INLINE text #-}
instance (CharParsing m, MonadPlus m) => CharParsing (Strict.StateT s m) where
satisfy = lift . satisfy
{-# INLINE satisfy #-}
char = lift . char
{-# INLINE char #-}
notChar = lift . notChar
{-# INLINE notChar #-}
anyChar = lift anyChar
{-# INLINE anyChar #-}
string = lift . string
{-# INLINE string #-}
text = lift . text
{-# INLINE text #-}
instance (CharParsing m, MonadPlus m) => CharParsing (ReaderT e m) where
satisfy = lift . satisfy
{-# INLINE satisfy #-}
char = lift . char
{-# INLINE char #-}
notChar = lift . notChar
{-# INLINE notChar #-}
anyChar = lift anyChar
{-# INLINE anyChar #-}
string = lift . string
{-# INLINE string #-}
text = lift . text
{-# INLINE text #-}
instance (CharParsing m, MonadPlus m, Monoid w) => CharParsing (Strict.WriterT w m) where
satisfy = lift . satisfy
{-# INLINE satisfy #-}
char = lift . char
{-# INLINE char #-}
notChar = lift . notChar
{-# INLINE notChar #-}
anyChar = lift anyChar
{-# INLINE anyChar #-}
string = lift . string
{-# INLINE string #-}
text = lift . text
{-# INLINE text #-}
instance (CharParsing m, MonadPlus m, Monoid w) => CharParsing (Lazy.WriterT w m) where
satisfy = lift . satisfy
{-# INLINE satisfy #-}
char = lift . char
{-# INLINE char #-}
notChar = lift . notChar
{-# INLINE notChar #-}
anyChar = lift anyChar
{-# INLINE anyChar #-}
string = lift . string
{-# INLINE string #-}
text = lift . text
{-# INLINE text #-}
instance (CharParsing m, MonadPlus m, Monoid w) => CharParsing (Lazy.RWST r w s m) where
satisfy = lift . satisfy
{-# INLINE satisfy #-}
char = lift . char
{-# INLINE char #-}
notChar = lift . notChar
{-# INLINE notChar #-}
anyChar = lift anyChar
{-# INLINE anyChar #-}
string = lift . string
{-# INLINE string #-}
text = lift . text
{-# INLINE text #-}
instance (CharParsing m, MonadPlus m, Monoid w) => CharParsing (Strict.RWST r w s m) where
satisfy = lift . satisfy
{-# INLINE satisfy #-}
char = lift . char
{-# INLINE char #-}
notChar = lift . notChar
{-# INLINE notChar #-}
anyChar = lift anyChar
{-# INLINE anyChar #-}
string = lift . string
{-# INLINE string #-}
text = lift . text
{-# INLINE text #-}
instance (CharParsing m, MonadPlus m) => CharParsing (IdentityT m) where
satisfy = lift . satisfy
{-# INLINE satisfy #-}
char = lift . char
{-# INLINE char #-}
notChar = lift . notChar
{-# INLINE notChar #-}
anyChar = lift anyChar
{-# INLINE anyChar #-}
string = lift . string
{-# INLINE string #-}
text = lift . text
{-# INLINE 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 t ~ Char => CharParsing (ReadP.Parser r t) where
satisfy = ReadP.satisfy
char = ReadP.char
notChar c = ReadP.satisfy (/= c)
anyChar = ReadP.get
string = ReadP.string
integral :: (CharParsing m, Integral a) => m a
integral = toNumber <$> some d <?> "integral"
where
toNumber = foldl' (\a b -> a * 10 + b) 0
d = f <$> satisfyRange '0' '9'
f '0' = 0
f '1' = 1
f '2' = 2
f '3' = 3
f '4' = 4
f '5' = 5
f '6' = 6
f '7' = 7
f '8' = 8
f '9' = 9
f _ = error "panic! integral"
{-# INLINE integral #-}
munch1 :: CharParsing m => (Char -> Bool) -> m String
munch1 = some . satisfy
{-# INLINE munch1 #-}
munch :: CharParsing m => (Char -> Bool) -> m String
munch = many . satisfy
{-# INLINE munch #-}
skipSpaces1 :: CharParsing m => m ()
skipSpaces1 = skipSome space
{-# INLINE skipSpaces1 #-}