{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeFamilies #-}
module Text.Megaparsec.Byte
(
newline,
crlf,
eol,
tab,
space,
hspace,
space1,
hspace1,
controlChar,
spaceChar,
upperChar,
lowerChar,
letterChar,
alphaNumChar,
printChar,
digitChar,
binDigitChar,
octDigitChar,
hexDigitChar,
asciiChar,
char,
char',
string,
string',
)
where
import Control.Applicative
import Data.Char hiding (isSpace, toLower, toUpper)
import Data.Functor (void)
import Data.Proxy
import Data.Word (Word8)
import Text.Megaparsec
import Text.Megaparsec.Common
newline :: (MonadParsec e s m, Token s ~ Word8) => m (Token s)
newline = char 10
{-# INLINE newline #-}
crlf :: forall e s m. (MonadParsec e s m, Token s ~ Word8) => m (Tokens s)
crlf = string (tokensToChunk (Proxy :: Proxy s) [13, 10])
{-# INLINE crlf #-}
eol :: forall e s m. (MonadParsec e s m, Token s ~ Word8) => m (Tokens s)
eol =
(tokenToChunk (Proxy :: Proxy s) <$> newline)
<|> crlf
<?> "end of line"
{-# INLINE eol #-}
tab :: (MonadParsec e s m, Token s ~ Word8) => m (Token s)
tab = char 9
{-# INLINE tab #-}
space :: (MonadParsec e s m, Token s ~ Word8) => m ()
space = void $ takeWhileP (Just "white space") isSpace
{-# INLINE space #-}
hspace :: (MonadParsec e s m, Token s ~ Word8) => m ()
hspace = void $ takeWhileP (Just "white space") isHSpace
{-# INLINE hspace #-}
space1 :: (MonadParsec e s m, Token s ~ Word8) => m ()
space1 = void $ takeWhile1P (Just "white space") isSpace
{-# INLINE space1 #-}
hspace1 :: (MonadParsec e s m, Token s ~ Word8) => m ()
hspace1 = void $ takeWhile1P (Just "white space") isHSpace
{-# INLINE hspace1 #-}
controlChar :: (MonadParsec e s m, Token s ~ Word8) => m (Token s)
controlChar = satisfy (isControl . toChar) <?> "control character"
{-# INLINE controlChar #-}
spaceChar :: (MonadParsec e s m, Token s ~ Word8) => m (Token s)
spaceChar = satisfy isSpace <?> "white space"
{-# INLINE spaceChar #-}
upperChar :: (MonadParsec e s m, Token s ~ Word8) => m (Token s)
upperChar = satisfy (isUpper . toChar) <?> "uppercase letter"
{-# INLINE upperChar #-}
lowerChar :: (MonadParsec e s m, Token s ~ Word8) => m (Token s)
lowerChar = satisfy (isLower . toChar) <?> "lowercase letter"
{-# INLINE lowerChar #-}
letterChar :: (MonadParsec e s m, Token s ~ Word8) => m (Token s)
letterChar = satisfy (isLetter . toChar) <?> "letter"
{-# INLINE letterChar #-}
alphaNumChar :: (MonadParsec e s m, Token s ~ Word8) => m (Token s)
alphaNumChar = satisfy (isAlphaNum . toChar) <?> "alphanumeric character"
{-# INLINE alphaNumChar #-}
printChar :: (MonadParsec e s m, Token s ~ Word8) => m (Token s)
printChar = satisfy (isPrint . toChar) <?> "printable character"
{-# INLINE printChar #-}
digitChar :: (MonadParsec e s m, Token s ~ Word8) => m (Token s)
digitChar = satisfy isDigit' <?> "digit"
where
isDigit' x = x >= 48 && x <= 57
{-# INLINE digitChar #-}
binDigitChar :: (MonadParsec e s m, Token s ~ Word8) => m (Token s)
binDigitChar = satisfy isBinDigit <?> "binary digit"
where
isBinDigit x = x == 48 || x == 49
{-# INLINE binDigitChar #-}
octDigitChar :: (MonadParsec e s m, Token s ~ Word8) => m (Token s)
octDigitChar = satisfy isOctDigit' <?> "octal digit"
where
isOctDigit' x = x >= 48 && x <= 55
{-# INLINE octDigitChar #-}
hexDigitChar :: (MonadParsec e s m, Token s ~ Word8) => m (Token s)
hexDigitChar = satisfy (isHexDigit . toChar) <?> "hexadecimal digit"
{-# INLINE hexDigitChar #-}
asciiChar :: (MonadParsec e s m, Token s ~ Word8) => m (Token s)
asciiChar = satisfy (< 128) <?> "ASCII character"
{-# INLINE asciiChar #-}
char :: (MonadParsec e s m, Token s ~ Word8) => Token s -> m (Token s)
char = single
{-# INLINE char #-}
char' :: (MonadParsec e s m, Token s ~ Word8) => Token s -> m (Token s)
char' c =
choice
[ char (toLower c),
char (toUpper c)
]
{-# INLINE char' #-}
isSpace :: Word8 -> Bool
isSpace x
| x >= 9 && x <= 13 = True
| x == 32 = True
| x == 160 = True
| otherwise = False
{-# INLINE isSpace #-}
isHSpace :: Word8 -> Bool
isHSpace x
| x == 9 = True
| x == 11 = True
| x == 12 = True
| x == 32 = True
| x == 160 = True
| otherwise = False
{-# INLINE isHSpace #-}
toChar :: Word8 -> Char
toChar = chr . fromIntegral
{-# INLINE toChar #-}
toUpper :: Word8 -> Word8
toUpper x
| x >= 97 && x <= 122 = x - 32
| x == 247 = x
| x == 255 = x
| x >= 224 = x - 32
| otherwise = x
{-# INLINE toUpper #-}
toLower :: Word8 -> Word8
toLower x
| x >= 65 && x <= 90 = x + 32
| x == 215 = x
| x >= 192 && x <= 222 = x + 32
| otherwise = x
{-# INLINE toLower #-}