{-# language MagicHash #-}
{-# language BlockArguments #-}
{-# language UnboxedTuples #-}
{-# language BangPatterns #-}
{-# language TypeApplications #-}
{-# language NegativeLiterals #-}
{-# language UnliftedFFITypes #-}
{-# language ScopedTypeVariables #-}
{-# language ForeignFunctionInterface #-}
module Text.Parsnip.Char8
( satisfy
, char
, notChar
, anyChar
, digit
, space
, skipSpace
, letter_ascii
, letter_iso8859_15
, while, whileSome
, till, tillSome, tillChar
, skipWhile, skipWhileSome
, skipTill, skipTillSome, skipTillChar
, previousChar, previousChar'
, nextChar, nextChar'
) where
import Control.Applicative
import qualified Data.Attoparsec.ByteString.Char8 as A
import Data.ByteString (ByteString)
import Data.Word
import GHC.Char
import GHC.Prim
import GHC.Ptr
import GHC.Types
import Text.Parsnip.Internal.Parser
import Text.Parsnip.Internal.Private
import Text.Parsnip.Parser
satisfy :: (Char -> Bool) -> Parser s Char
satisfy :: forall s. (Char -> Bool) -> Parser s Char
satisfy Char -> Bool
f = (Addr# -> State# s -> Result s Char) -> Parser s Char
forall s a. (Addr# -> State# s -> Result s a) -> Parser s a
Parser \Addr#
p State# s
s -> case Addr# -> Int# -> State# s -> (# State# s, Char# #)
forall d. Addr# -> Int# -> State# d -> (# State# d, Char# #)
readCharOffAddr# Addr#
p Int#
0# State# s
s of
(# State# s
t, Char#
c #) -> if Int# -> Bool
isTrue# (Int# -> Char#
chr# Int#
0# Char# -> Char# -> Int#
`neChar#` Char#
c) Bool -> Bool -> Bool
&& Char -> Bool
f (Char# -> Char
C# Char#
c)
then Char -> Addr# -> State# s -> Result s Char
forall a s. a -> Addr# -> State# s -> Result s a
OK (Char# -> Char
C# Char#
c) (Addr# -> Int# -> Addr#
plusAddr# Addr#
p Int#
1#) State# s
t
else Addr# -> State# s -> Result s Char
forall s a. Addr# -> State# s -> Result s a
Fail Addr#
p State# s
t
{-# inline satisfy #-}
char :: Char -> Parser s Char
char :: forall s. Char -> Parser s Char
char Char
'\0' = Parser s Char
forall (f :: * -> *) a. Alternative f => f a
empty
char r :: Char
r@(C# Char#
c) = (Addr# -> State# s -> Result s Char) -> Parser s Char
forall s a. (Addr# -> State# s -> Result s a) -> Parser s a
Parser \Addr#
p State# s
s -> case Addr# -> Int# -> State# s -> (# State# s, Char# #)
forall d. Addr# -> Int# -> State# d -> (# State# d, Char# #)
readCharOffAddr# Addr#
p Int#
0# State# s
s of
(# State# s
t, Char#
c' #) -> if Int# -> Bool
isTrue# (Char# -> Char# -> Int#
eqChar# Char#
c Char#
c')
then Char -> Addr# -> State# s -> Result s Char
forall a s. a -> Addr# -> State# s -> Result s a
OK Char
r (Addr# -> Int# -> Addr#
plusAddr# Addr#
p Int#
1#) State# s
t
else Addr# -> State# s -> Result s Char
forall s a. Addr# -> State# s -> Result s a
Fail Addr#
p State# s
t
{-# inline char #-}
notChar :: Char -> Parser s Char
notChar :: forall s. Char -> Parser s Char
notChar Char
'\0' = Parser s Char
forall s. Parser s Char
anyChar
notChar (C# Char#
c) = (Addr# -> State# s -> Result s Char) -> Parser s Char
forall s a. (Addr# -> State# s -> Result s a) -> Parser s a
Parser \Addr#
p State# s
s -> case Addr# -> Int# -> State# s -> (# State# s, Char# #)
forall d. Addr# -> Int# -> State# d -> (# State# d, Char# #)
readCharOffAddr# Addr#
p Int#
0# State# s
s of
(# State# s
t, Char#
c' #) -> if Int# -> Bool
isTrue# (Int# -> Char#
chr# Int#
0# Char# -> Char# -> Int#
`neChar#` Char#
c') Bool -> Bool -> Bool
&& Int# -> Bool
isTrue# (Char# -> Char# -> Int#
neChar# Char#
c Char#
c')
then Char -> Addr# -> State# s -> Result s Char
forall a s. a -> Addr# -> State# s -> Result s a
OK (Char# -> Char
C# Char#
c') (Addr# -> Int# -> Addr#
plusAddr# Addr#
p Int#
1#) State# s
t
else Addr# -> State# s -> Result s Char
forall s a. Addr# -> State# s -> Result s a
Fail Addr#
p State# s
t
{-# inline notChar #-}
nextChar :: Parser s (Maybe Char)
nextChar :: forall s. Parser s (Maybe Char)
nextChar = (Addr# -> State# s -> Result s (Maybe Char))
-> Parser s (Maybe Char)
forall s a. (Addr# -> State# s -> Result s a) -> Parser s a
Parser \Addr#
p State# s
s -> case Addr# -> Int# -> State# s -> (# State# s, Char# #)
forall d. Addr# -> Int# -> State# d -> (# State# d, Char# #)
readCharOffAddr# Addr#
p Int#
0# State# s
s of
(# State# s
t, Char#
c #) -> Maybe Char -> Addr# -> State# s -> Result s (Maybe Char)
forall a s. a -> Addr# -> State# s -> Result s a
OK (if Int# -> Bool
isTrue# (Int# -> Char#
chr# Int#
0# Char# -> Char# -> Int#
`neChar#` Char#
c) then Char -> Maybe Char
forall a. a -> Maybe a
Just (Char# -> Char
C# Char#
c) else Maybe Char
forall a. Maybe a
Nothing) Addr#
p State# s
t
{-# inline nextChar #-}
nextChar' :: Parser s Char
nextChar' :: forall s. Parser s Char
nextChar' = (Addr# -> State# s -> Result s Char) -> Parser s Char
forall s a. (Addr# -> State# s -> Result s a) -> Parser s a
Parser \Addr#
p State# s
s -> case Addr# -> Int# -> State# s -> (# State# s, Char# #)
forall d. Addr# -> Int# -> State# d -> (# State# d, Char# #)
readCharOffAddr# Addr#
p Int#
0# State# s
s of
(# State# s
t, Char#
c #) -> if Int# -> Bool
isTrue# (Int# -> Char#
chr# Int#
0# Char# -> Char# -> Int#
`neChar#` Char#
c)
then Char -> Addr# -> State# s -> Result s Char
forall a s. a -> Addr# -> State# s -> Result s a
OK (Char# -> Char
C# Char#
c) Addr#
p State# s
t
else Addr# -> State# s -> Result s Char
forall s a. Addr# -> State# s -> Result s a
Fail Addr#
p State# s
t
{-# inline nextChar' #-}
anyChar :: Parser s Char
anyChar :: forall s. Parser s Char
anyChar = (Addr# -> State# s -> Result s Char) -> Parser s Char
forall s a. (Addr# -> State# s -> Result s a) -> Parser s a
Parser \Addr#
p State# s
s -> case Addr# -> Int# -> State# s -> (# State# s, Char# #)
forall d. Addr# -> Int# -> State# d -> (# State# d, Char# #)
readCharOffAddr# Addr#
p Int#
0# State# s
s of
(# State# s
t, Char#
c #) -> if Int# -> Bool
isTrue# (Int# -> Char#
chr# Int#
0# Char# -> Char# -> Int#
`neChar#` Char#
c)
then Char -> Addr# -> State# s -> Result s Char
forall a s. a -> Addr# -> State# s -> Result s a
OK (Char# -> Char
C# Char#
c) (Addr# -> Int# -> Addr#
plusAddr# Addr#
p Int#
1#) State# s
t
else Addr# -> State# s -> Result s Char
forall s a. Addr# -> State# s -> Result s a
Fail Addr#
p State# s
t
{-# inline anyChar #-}
digit :: Parser s Char
digit :: forall s. Parser s Char
digit = (Char -> Bool) -> Parser s Char
forall s. (Char -> Bool) -> Parser s Char
satisfy Char -> Bool
A.isDigit
{-# inline digit #-}
space :: Parser s Char
space :: forall s. Parser s Char
space = (Char -> Bool) -> Parser s Char
forall s. (Char -> Bool) -> Parser s Char
satisfy Char -> Bool
A.isSpace
{-# inline space #-}
skipSpace :: Parser s ()
skipSpace :: forall s. Parser s ()
skipSpace = (Char -> Bool) -> Parser s ()
forall s. (Char -> Bool) -> Parser s ()
skipWhile Char -> Bool
A.isSpace
{-# inline skipSpace #-}
letter_ascii :: Parser s Char
letter_ascii :: forall s. Parser s Char
letter_ascii = (Char -> Bool) -> Parser s Char
forall s. (Char -> Bool) -> Parser s Char
satisfy Char -> Bool
A.isAlpha_ascii
{-# inline letter_ascii #-}
letter_iso8859_15:: Parser s Char
letter_iso8859_15 :: forall s. Parser s Char
letter_iso8859_15 = (Char -> Bool) -> Parser s Char
forall s. (Char -> Bool) -> Parser s Char
satisfy Char -> Bool
A.isAlpha_iso8859_15
{-# inline letter_iso8859_15 #-}
scan :: (Char -> Bool) -> Addr# -> State# s -> (# State# s, Addr# #)
scan :: forall s.
(Char -> Bool) -> Addr# -> State# s -> (# State# s, Addr# #)
scan Char -> Bool
f = Addr# -> State# s -> (# State# s, Addr# #)
forall {s}. Addr# -> State# s -> (# State# s, Addr# #)
go where
go :: Addr# -> State# s -> (# State# s, Addr# #)
go Addr#
p State# s
s = case Addr# -> Int# -> State# s -> (# State# s, Char# #)
forall d. Addr# -> Int# -> State# d -> (# State# d, Char# #)
readCharOffAddr# Addr#
p Int#
0# State# s
s of
(# State# s
t, Char#
c #) -> if Int# -> Bool
isTrue# (Int# -> Char#
chr# Int#
0# Char# -> Char# -> Int#
`neChar#` Char#
c) Bool -> Bool -> Bool
&& Char -> Bool
f (Char# -> Char
C# Char#
c)
then (# State# s
t, Addr#
p #)
else (Char -> Bool) -> Addr# -> State# s -> (# State# s, Addr# #)
forall s.
(Char -> Bool) -> Addr# -> State# s -> (# State# s, Addr# #)
scan Char -> Bool
f (Addr# -> Int# -> Addr#
plusAddr# Addr#
p Int#
1#) State# s
t
{-# inline scan #-}
skipWhile :: (Char -> Bool) -> Parser s ()
skipWhile :: forall s. (Char -> Bool) -> Parser s ()
skipWhile Char -> Bool
f = (Addr# -> State# s -> Result s ()) -> Parser s ()
forall s a. (Addr# -> State# s -> Result s a) -> Parser s a
Parser \Addr#
p State# s
s -> case (Char -> Bool) -> Addr# -> State# s -> (# State# s, Addr# #)
forall s.
(Char -> Bool) -> Addr# -> State# s -> (# State# s, Addr# #)
scan Char -> Bool
f Addr#
p State# s
s of
(# State# s
t, Addr#
q #) -> () -> Addr# -> State# s -> Result s ()
forall a s. a -> Addr# -> State# s -> Result s a
OK () Addr#
q State# s
t
{-# inline [1] skipWhile #-}
{-# RULES
"skipWhile (x/=)" forall x.
skipWhile (x `neChar`) = skipTillChar x
"skipWhile (/=x)" forall x.
skipWhile (`neChar` x) = skipTillChar x
#-}
skipTill :: (Char -> Bool) -> Parser s ()
skipTill :: forall s. (Char -> Bool) -> Parser s ()
skipTill Char -> Bool
p = (Char -> Bool) -> Parser s ()
forall s. (Char -> Bool) -> Parser s ()
skipWhile (Bool -> Bool
not (Bool -> Bool) -> (Char -> Bool) -> Char -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> Bool
p)
{-# inline [1] skipTill #-}
{-# RULES
"skipTill (x==)" forall x.
skipTill (x `eqChar`) = skipTillChar x
"skipWhile (==x)" forall x.
skipWhile (`eqChar` x) = skipTillChar x
#-}
skipTillSome :: (Char -> Bool) -> Parser s ()
skipTillSome :: forall s. (Char -> Bool) -> Parser s ()
skipTillSome Char -> Bool
p = (Char -> Bool) -> Parser s ()
forall s. (Char -> Bool) -> Parser s ()
skipWhileSome (Bool -> Bool
not (Bool -> Bool) -> (Char -> Bool) -> Char -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> Bool
p)
{-# inline skipTillSome #-}
foreign import ccall "parsnip.h" strchr0 :: Addr# -> Char# -> IO (Ptr Word8)
skipTillChar :: Char -> Parser s ()
skipTillChar :: forall s. Char -> Parser s ()
skipTillChar (C# Char#
c) = (Addr# -> State# s -> Result s ()) -> Parser s ()
forall s a. (Addr# -> State# s -> Result s a) -> Parser s a
Parser ((Addr# -> State# s -> Result s ()) -> Parser s ())
-> (Addr# -> State# s -> Result s ()) -> Parser s ()
forall a b. (a -> b) -> a -> b
$ \Addr#
p State# s
s -> case IO (Ptr Word8) -> State# s -> (# State# s, Ptr Word8 #)
forall a s. IO a -> State# s -> (# State# s, a #)
io (Addr# -> Char# -> IO (Ptr Word8)
strchr0 Addr#
p Char#
c) State# s
s of
(# State# s
t, Ptr Addr#
q #) -> () -> Addr# -> State# s -> Result s ()
forall a s. a -> Addr# -> State# s -> Result s a
OK () Addr#
q State# s
t
{-# inline skipTillChar #-}
skipWhileSome :: (Char -> Bool) -> Parser s ()
skipWhileSome :: forall s. (Char -> Bool) -> Parser s ()
skipWhileSome Char -> Bool
p = (Char -> Bool) -> Parser s Char
forall s. (Char -> Bool) -> Parser s Char
satisfy Char -> Bool
p Parser s Char -> Parser s () -> Parser s ()
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> (Char -> Bool) -> Parser s ()
forall s. (Char -> Bool) -> Parser s ()
skipWhile Char -> Bool
p
{-# inline skipWhileSome #-}
while :: KnownBase s => (Char -> Bool) -> Parser s ByteString
while :: forall s. KnownBase s => (Char -> Bool) -> Parser s ByteString
while Char -> Bool
f = Parser s () -> Parser s ByteString
forall s a. KnownBase s => Parser s a -> Parser s ByteString
snipping ((Char -> Bool) -> Parser s ()
forall s. (Char -> Bool) -> Parser s ()
skipWhile Char -> Bool
f)
{-# inline while #-}
till :: KnownBase s => (Char -> Bool) -> Parser s ByteString
till :: forall s. KnownBase s => (Char -> Bool) -> Parser s ByteString
till Char -> Bool
p = Parser s () -> Parser s ByteString
forall s a. KnownBase s => Parser s a -> Parser s ByteString
snipping ((Char -> Bool) -> Parser s ()
forall s. (Char -> Bool) -> Parser s ()
skipTill Char -> Bool
p)
{-# inline till #-}
tillChar :: KnownBase s => Char -> Parser s ByteString
tillChar :: forall s. KnownBase s => Char -> Parser s ByteString
tillChar Char
c = Parser s () -> Parser s ByteString
forall s a. KnownBase s => Parser s a -> Parser s ByteString
snipping (Char -> Parser s ()
forall s. Char -> Parser s ()
skipTillChar Char
c)
{-# inline tillChar #-}
whileSome :: KnownBase s => (Char -> Bool) -> Parser s ByteString
whileSome :: forall s. KnownBase s => (Char -> Bool) -> Parser s ByteString
whileSome Char -> Bool
p = Parser s () -> Parser s ByteString
forall s a. KnownBase s => Parser s a -> Parser s ByteString
snipping ((Char -> Bool) -> Parser s ()
forall s. (Char -> Bool) -> Parser s ()
skipWhileSome Char -> Bool
p)
{-# inline whileSome #-}
tillSome :: KnownBase s => (Char -> Bool) -> Parser s ByteString
tillSome :: forall s. KnownBase s => (Char -> Bool) -> Parser s ByteString
tillSome Char -> Bool
p = Parser s () -> Parser s ByteString
forall s a. KnownBase s => Parser s a -> Parser s ByteString
snipping ((Char -> Bool) -> Parser s ()
forall s. (Char -> Bool) -> Parser s ()
skipTillSome Char -> Bool
p)
{-# inline tillSome #-}
previousChar :: forall s. KnownBase s => Parser s (Maybe Char)
previousChar :: forall s. KnownBase s => Parser s (Maybe Char)
previousChar = case forall s. KnownBase s => Base s
reflectBase @s of
!(Base Addr#
_ ForeignPtrContents
_ Addr#
l Addr#
_) -> (Addr# -> State# s -> Result s (Maybe Char))
-> Parser s (Maybe Char)
forall s a. (Addr# -> State# s -> Result s a) -> Parser s a
Parser \Addr#
p State# s
s ->
if Int# -> Bool
isTrue# (Addr# -> Addr# -> Int#
ltAddr# Addr#
l Addr#
p)
then case Addr# -> Int# -> State# s -> (# State# s, Char# #)
forall d. Addr# -> Int# -> State# d -> (# State# d, Char# #)
readCharOffAddr# Addr#
p (Int#
-1#) State# s
s of
(# State# s
t, Char#
c #) -> Maybe Char -> Addr# -> State# s -> Result s (Maybe Char)
forall a s. a -> Addr# -> State# s -> Result s a
OK (Char -> Maybe Char
forall a. a -> Maybe a
Just (Char# -> Char
C# Char#
c)) Addr#
p State# s
t
else Maybe Char -> Addr# -> State# s -> Result s (Maybe Char)
forall a s. a -> Addr# -> State# s -> Result s a
OK Maybe Char
forall a. Maybe a
Nothing Addr#
p State# s
s
previousChar' :: forall s. KnownBase s => Parser s Char
previousChar' :: forall s. KnownBase s => Parser s Char
previousChar' = case forall s. KnownBase s => Base s
reflectBase @s of
!(Base Addr#
_ ForeignPtrContents
_ Addr#
l Addr#
_) -> (Addr# -> State# s -> Result s Char) -> Parser s Char
forall s a. (Addr# -> State# s -> Result s a) -> Parser s a
Parser \Addr#
p State# s
s ->
if Int# -> Bool
isTrue# (Addr# -> Addr# -> Int#
ltAddr# Addr#
l Addr#
p)
then case Addr# -> Int# -> State# s -> (# State# s, Char# #)
forall d. Addr# -> Int# -> State# d -> (# State# d, Char# #)
readCharOffAddr# Addr#
p (Int#
-1#) State# s
s of
(# State# s
t, Char#
c #) -> Char -> Addr# -> State# s -> Result s Char
forall a s. a -> Addr# -> State# s -> Result s a
OK (Char# -> Char
C# Char#
c) Addr#
p State# s
t
else Addr# -> State# s -> Result s Char
forall s a. Addr# -> State# s -> Result s a
Fail Addr#
p State# s
s