{-# LANGUAGE UnboxedTuples #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE ScopedTypeVariables #-}
module FlatParse.Basic (
FP.Parser.ParserT(..)
, FP.Parser.Parser, FP.Parser.ParserIO, FP.Parser.ParserST
, Result(..)
, runParser
, runParserUtf8
, runParserIO
, runParserST
, embedParserST
, type FP.Parser.Res#
, pattern FP.Parser.OK#, pattern FP.Parser.Err#, pattern FP.Parser.Fail#
, type FP.Parser.ResI#
, liftST
, Common.strToUtf8
, Common.utf8ToStr
, Common.isDigit
, Common.isLatinLetter
, Common.isGreekLetter
, FP.Base.eof
, FP.Base.take
, FP.Base.take#
, FP.Base.takeUnsafe#
, FP.Base.takeRest
, FP.Base.skip
, FP.Base.skip#
, FP.Base.skipBack
, FP.Base.skipBack#
, FP.Base.atSkip#
, FP.Base.atSkipUnsafe#
, FP.Bytes.bytes
, FP.Bytes.bytesUnsafe
, byteString
, anyCString
, anyVarintProtobuf
, (FP.Parser.<|>)
, FP.Base.branch
, FP.Base.notFollowedBy
, FP.Base.chainl
, FP.Base.chainr
, FP.Base.lookahead
, FP.Base.ensure
, FP.Base.ensure#
, FP.Base.withEnsure
, FP.Base.withEnsure1
, FP.Base.withEnsure#
, FP.Base.isolate
, isolateToNextNull
, FP.Base.isolate#
, FP.Base.isolateUnsafe#
, FP.Switch.switch
, FP.Switch.switchWithPost
, FP.Switch.rawSwitchWithPost
, Control.Applicative.many
, FP.Base.skipMany
, Control.Applicative.some
, FP.Base.skipSome
, Control.Applicative.empty
, FP.Base.failed
, FP.Base.try
, FP.Base.err
, FP.Base.withError
, FP.Base.withAnyResult
, FP.Base.fails
, FP.Base.cut
, FP.Base.cutting
, FP.Base.optional
, FP.Base.optional_
, FP.Base.withOption
, FlatParse.Common.Position.Pos(..)
, FlatParse.Common.Position.endPos
, FlatParse.Common.Position.addrToPos#
, FlatParse.Common.Position.posToAddr#
, FlatParse.Common.Position.Span(..)
, FlatParse.Common.Position.unsafeSlice
, getPos
, setPos
, spanOf
, withSpan
, byteStringOf
, withByteString
, inSpan
, validPos
, posLineCols
, mkPos
, FP.Text.char, FP.Text.string
, FP.Text.anyChar, FP.Text.skipAnyChar
, FP.Text.satisfy, FP.Text.skipSatisfy
, FP.Text.fusedSatisfy, FP.Text.skipFusedSatisfy
, FP.Text.takeLine
, FP.Text.takeRestString
, linesUtf8
, FP.Text.anyAsciiChar, FP.Text.skipAnyAsciiChar
, FP.Text.satisfyAscii, FP.Text.skipSatisfyAscii
, FP.Text.anyAsciiDecimalWord
, FP.Text.anyAsciiDecimalInt
, FP.Text.anyAsciiDecimalInteger
, FP.Text.anyAsciiHexWord
, FP.Text.anyAsciiHexInt
, module FP.Integers
, FP.Text.traceLine
, FP.Text.traceRest
, unsafeSpanToByteString
, unsafeLiftIO
, module FP.Addr
, anyCStringUnsafe
) where
#include "MachDeps.h"
import FlatParse.Basic.Parser
import FlatParse.Basic.Base
import FlatParse.Basic.Integers
import FlatParse.Basic.Text
import FlatParse.Basic.Addr
import FlatParse.Common.Position
import qualified FlatParse.Common.Assorted as Common
import qualified FlatParse.Common.Numbers as Common
import qualified FlatParse.Basic.Parser as FP.Parser
import qualified FlatParse.Basic.Base as FP.Base
import qualified FlatParse.Basic.Integers as FP.Integers
import qualified FlatParse.Basic.Bytes as FP.Bytes
import qualified FlatParse.Basic.Text as FP.Text
import qualified FlatParse.Basic.Switch as FP.Switch
import qualified FlatParse.Basic.Addr as FP.Addr
import qualified Control.Applicative
import GHC.IO (IO(..), unsafeIOToST)
import GHC.Exts
import GHC.ForeignPtr
import GHC.ST (ST(..))
import System.IO.Unsafe
import Data.Ord ( comparing )
import Data.List ( sortBy )
import qualified Data.ByteString as B
import qualified Data.ByteString.Unsafe as B
import qualified Data.ByteString.Internal as B
data Result e a =
OK a !(B.ByteString)
| Fail
| Err !e
deriving Int -> Result e a -> ShowS
[Result e a] -> ShowS
Result e a -> String
(Int -> Result e a -> ShowS)
-> (Result e a -> String)
-> ([Result e a] -> ShowS)
-> Show (Result e a)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
forall e a. (Show a, Show e) => Int -> Result e a -> ShowS
forall e a. (Show a, Show e) => [Result e a] -> ShowS
forall e a. (Show a, Show e) => Result e a -> String
$cshowsPrec :: forall e a. (Show a, Show e) => Int -> Result e a -> ShowS
showsPrec :: Int -> Result e a -> ShowS
$cshow :: forall e a. (Show a, Show e) => Result e a -> String
show :: Result e a -> String
$cshowList :: forall e a. (Show a, Show e) => [Result e a] -> ShowS
showList :: [Result e a] -> ShowS
Show
instance Functor (Result e) where
fmap :: forall a b. (a -> b) -> Result e a -> Result e b
fmap a -> b
f (OK a
a ByteString
s) = let !b :: b
b = a -> b
f a
a in b -> ByteString -> Result e b
forall e a. a -> ByteString -> Result e a
OK b
b ByteString
s
fmap a -> b
f Result e a
r = Result e a -> Result e b
forall a b. a -> b
unsafeCoerce# Result e a
r
{-# inline fmap #-}
<$ :: forall a b. a -> Result e b -> Result e a
(<$) a
a (OK b
_ ByteString
s) = a -> ByteString -> Result e a
forall e a. a -> ByteString -> Result e a
OK a
a ByteString
s
(<$) a
_ Result e b
r = Result e b -> Result e a
forall a b. a -> b
unsafeCoerce# Result e b
r
{-# inline (<$) #-}
unsafeLiftIO :: IO a -> ParserT st e a
unsafeLiftIO :: forall a (st :: ZeroBitType) e. IO a -> ParserT st e a
unsafeLiftIO IO a
io = (ForeignPtrContents -> Addr# -> Addr# -> st -> Res# st e a)
-> ParserT st e a
forall (st :: ZeroBitType) e a.
(ForeignPtrContents -> Addr# -> Addr# -> st -> Res# st e a)
-> ParserT st e a
ParserT \ForeignPtrContents
fp Addr#
eob Addr#
s st
st ->
let !a :: a
a = IO a -> a
forall a. IO a -> a
unsafePerformIO IO a
io
in st -> a -> Addr# -> Res# st e a
forall (st :: ZeroBitType) a e. st -> a -> Addr# -> Res# st e a
OK# st
st a
a Addr#
s
{-# inline unsafeLiftIO #-}
runParser :: Parser e a -> B.ByteString -> Result e a
runParser :: forall e a. Parser e a -> ByteString -> Result e a
runParser (ParserT ForeignPtrContents
-> Addr# -> Addr# -> PureMode -> Res# PureMode e a
f) b :: ByteString
b@(B.PS (ForeignPtr Addr#
_ ForeignPtrContents
fp) Int
_ (I# Int#
len)) = IO (Result e a) -> Result e a
forall a. IO a -> a
unsafePerformIO (IO (Result e a) -> Result e a) -> IO (Result e a) -> Result e a
forall a b. (a -> b) -> a -> b
$
ByteString -> (CString -> IO (Result e a)) -> IO (Result e a)
forall a. ByteString -> (CString -> IO a) -> IO a
B.unsafeUseAsCString ByteString
b \(Ptr Addr#
buf) -> do
let end :: Addr#
end = Addr# -> Int# -> Addr#
plusAddr# Addr#
buf Int#
len
Result e a -> IO (Result e a)
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure case ForeignPtrContents
-> Addr# -> Addr# -> PureMode -> Res# PureMode e a
f ForeignPtrContents
fp Addr#
end Addr#
buf PureMode
forall {k} (a :: k). Proxy# a
proxy# of
OK# PureMode
_st a
a Addr#
s -> let offset :: Int#
offset = Addr# -> Addr# -> Int#
minusAddr# Addr#
s Addr#
buf
in a -> ByteString -> Result e a
forall e a. a -> ByteString -> Result e a
OK a
a (Int -> ByteString -> ByteString
B.drop (Int# -> Int
I# Int#
offset) ByteString
b)
Err# PureMode
_st e
e -> e -> Result e a
forall e a. e -> Result e a
Err e
e
Fail# PureMode
_st -> Result e a
forall e a. Result e a
Fail
{-# noinline runParser #-}
runParserUtf8 :: Parser e a -> String -> Result e a
runParserUtf8 :: forall e a. Parser e a -> String -> Result e a
runParserUtf8 Parser e a
pa String
s = Parser e a -> ByteString -> Result e a
forall e a. Parser e a -> ByteString -> Result e a
runParser Parser e a
pa (String -> ByteString
Common.strToUtf8 String
s)
runParserST :: ParserST s e a -> B.ByteString -> ST s (Result e a)
runParserST :: forall s e a. ParserST s e a -> ByteString -> ST s (Result e a)
runParserST ParserST s e a
pst ByteString
buf = IO (Result e a) -> ST s (Result e a)
forall a s. IO a -> ST s a
unsafeIOToST (ParserIO e a -> ByteString -> IO (Result e a)
forall e a. ParserIO e a -> ByteString -> IO (Result e a)
runParserIO (ParserST s e a -> ParserIO e a
forall a b. a -> b
unsafeCoerce# ParserST s e a
pst) ByteString
buf)
{-# inlinable runParserST #-}
runParserIO :: ParserIO e a -> B.ByteString -> IO (Result e a)
runParserIO :: forall e a. ParserIO e a -> ByteString -> IO (Result e a)
runParserIO (ParserT ForeignPtrContents -> Addr# -> Addr# -> IOMode -> Res# IOMode e a
f) b :: ByteString
b@(B.PS (ForeignPtr Addr#
_ ForeignPtrContents
fp) Int
_ (I# Int#
len)) = do
ByteString -> (CString -> IO (Result e a)) -> IO (Result e a)
forall a. ByteString -> (CString -> IO a) -> IO a
B.unsafeUseAsCString ByteString
b \(Ptr Addr#
buf) -> do
let end :: Addr#
end = Addr# -> Int# -> Addr#
plusAddr# Addr#
buf Int#
len
(IOMode -> (# IOMode, Result e a #)) -> IO (Result e a)
forall a. (IOMode -> (# IOMode, a #)) -> IO a
IO \IOMode
st -> case ForeignPtrContents -> Addr# -> Addr# -> IOMode -> Res# IOMode e a
f ForeignPtrContents
fp Addr#
end Addr#
buf IOMode
st of
OK# IOMode
rw' a
a Addr#
s -> let offset :: Int#
offset = Addr# -> Addr# -> Int#
minusAddr# Addr#
s Addr#
buf
in (# IOMode
rw', a -> ByteString -> Result e a
forall e a. a -> ByteString -> Result e a
OK a
a (Int -> ByteString -> ByteString
B.drop (Int# -> Int
I# Int#
offset) ByteString
b) #)
Err# IOMode
rw' e
e -> (# IOMode
rw', e -> Result e a
forall e a. e -> Result e a
Err e
e #)
Fail# IOMode
rw' -> (# IOMode
rw', Result e a
forall e a. Result e a
Fail #)
{-# inlinable runParserIO #-}
liftST :: ST s a -> ParserST s e a
liftST :: forall s a e. ST s a -> ParserST s e a
liftST (ST STRep s a
f) = (ForeignPtrContents
-> Addr# -> Addr# -> STMode s -> Res# (STMode s) e a)
-> ParserT (STMode s) e a
forall (st :: ZeroBitType) e a.
(ForeignPtrContents -> Addr# -> Addr# -> st -> Res# st e a)
-> ParserT st e a
ParserT \ForeignPtrContents
fp Addr#
eob Addr#
s STMode s
st -> case STRep s a
f STMode s
st of
(# STMode s
st, a
a #) -> STMode s -> a -> Addr# -> Res# (STMode s) e a
forall (st :: ZeroBitType) a e. st -> a -> Addr# -> Res# st e a
OK# STMode s
st a
a Addr#
s
{-# inline liftST #-}
embedParserST :: forall e a. (forall s. ParserST s e a) -> Parser e a
embedParserST :: forall e a. (forall s. ParserST s e a) -> Parser e a
embedParserST forall s. ParserST s e a
f = ParserST RealWorld e a -> Parser e a
forall a b. a -> b
unsafeCoerce# (ParserST RealWorld e a
forall s. ParserST s e a
f :: ParserST RealWorld e a)
{-# inline embedParserST #-}
byteString :: B.ByteString -> ParserT st e ()
byteString :: forall (st :: ZeroBitType) e. ByteString -> ParserT st e ()
byteString (B.PS (ForeignPtr Addr#
bs ForeignPtrContents
fcontent) Int
_ (I# Int#
len)) =
let go64 :: Addr# -> Addr# -> Addr# -> State# RealWorld -> Res# (State# RealWorld) e ()
go64 :: forall e. Addr# -> Addr# -> Addr# -> IOMode -> Res# IOMode e ()
go64 Addr#
bs Addr#
bsend Addr#
s IOMode
rw =
let bs' :: Addr#
bs' = Addr# -> Int# -> Addr#
plusAddr# Addr#
bs Int#
8# in
case Addr# -> Addr# -> Int#
gtAddr# Addr#
bs' Addr#
bsend of
Int#
1# -> Addr# -> Addr# -> Addr# -> IOMode -> Res# IOMode e ()
forall e. Addr# -> Addr# -> Addr# -> IOMode -> Res# IOMode e ()
go8 Addr#
bs Addr#
bsend Addr#
s IOMode
rw
#if MIN_VERSION_base(4,17,0)
Int#
_ -> case Word64# -> Word64# -> Int#
eqWord64# (Addr# -> Int# -> Word64#
indexWord64OffAddr# Addr#
bs Int#
0#) (Addr# -> Int# -> Word64#
indexWord64OffAddr# Addr#
s Int#
0#) of
#else
_ -> case eqWord# (indexWord64OffAddr# bs 0#) (indexWord64OffAddr# s 0#) of
#endif
Int#
1# -> Addr# -> Addr# -> Addr# -> IOMode -> Res# IOMode e ()
forall e. Addr# -> Addr# -> Addr# -> IOMode -> Res# IOMode e ()
go64 Addr#
bs' Addr#
bsend (Addr# -> Int# -> Addr#
plusAddr# Addr#
s Int#
8#) IOMode
rw
Int#
_ -> IOMode -> Res# IOMode e ()
forall (st :: ZeroBitType) e a. st -> Res# st e a
Fail# IOMode
rw
go8 :: Addr# -> Addr# -> Addr# -> State# RealWorld -> Res# (State# RealWorld) e ()
go8 :: forall e. Addr# -> Addr# -> Addr# -> IOMode -> Res# IOMode e ()
go8 Addr#
bs Addr#
bsend Addr#
s IOMode
rw = case Addr# -> Addr# -> Int#
ltAddr# Addr#
bs Addr#
bsend of
#if MIN_VERSION_base(4,16,0)
Int#
1# -> case Word8# -> Word8# -> Int#
eqWord8# (Addr# -> Int# -> Word8#
indexWord8OffAddr# Addr#
bs Int#
0#) (Addr# -> Int# -> Word8#
indexWord8OffAddr# Addr#
s Int#
0#) of
#else
1# -> case eqWord# (indexWord8OffAddr# bs 0#) (indexWord8OffAddr# s 0#) of
#endif
Int#
1# -> Addr# -> Addr# -> Addr# -> IOMode -> Res# IOMode e ()
forall e. Addr# -> Addr# -> Addr# -> IOMode -> Res# IOMode e ()
go8 (Addr# -> Int# -> Addr#
plusAddr# Addr#
bs Int#
1#) Addr#
bsend (Addr# -> Int# -> Addr#
plusAddr# Addr#
s Int#
1#) IOMode
rw
Int#
_ -> IOMode -> Res# IOMode e ()
forall (st :: ZeroBitType) e a. st -> Res# st e a
Fail# IOMode
rw
Int#
_ -> IOMode -> () -> Addr# -> Res# IOMode e ()
forall (st :: ZeroBitType) a e. st -> a -> Addr# -> Res# st e a
OK# IOMode
rw () Addr#
s
go :: Addr# -> Addr# -> Addr# -> State# RealWorld -> Res# (State# RealWorld) e ()
go :: forall e. Addr# -> Addr# -> Addr# -> IOMode -> Res# IOMode e ()
go Addr#
bs Addr#
bsend Addr#
s IOMode
rw = case Addr# -> Addr# -> Addr# -> IOMode -> Res# IOMode e ()
forall e. Addr# -> Addr# -> Addr# -> IOMode -> Res# IOMode e ()
go64 Addr#
bs Addr#
bsend Addr#
s IOMode
rw of
(# IOMode
rw', ResI# e ()
res #) -> case ForeignPtrContents -> IOMode -> IOMode
forall a. a -> IOMode -> IOMode
touch# ForeignPtrContents
fcontent IOMode
rw' of
IOMode
rw'' -> (# IOMode
rw'', ResI# e ()
res #)
in (ForeignPtrContents -> Addr# -> Addr# -> st -> Res# st e ())
-> ParserT st e ()
forall (st :: ZeroBitType) e a.
(ForeignPtrContents -> Addr# -> Addr# -> st -> Res# st e a)
-> ParserT st e a
ParserT \ForeignPtrContents
fp Addr#
eob Addr#
s st
st ->
case Int#
len Int# -> Int# -> Int#
<=# Addr# -> Addr# -> Int#
minusAddr# Addr#
eob Addr#
s of
Int#
1# -> case (IOMode -> Res# IOMode e ()) -> Res# IOMode e ()
forall o. (IOMode -> o) -> o
runRW# (Addr# -> Addr# -> Addr# -> IOMode -> Res# IOMode e ()
forall e. Addr# -> Addr# -> Addr# -> IOMode -> Res# IOMode e ()
go Addr#
bs (Addr# -> Int# -> Addr#
plusAddr# Addr#
bs Int#
len) Addr#
s) of
(# IOMode
rw, ResI# e ()
a #) -> (# st
st, ResI# e ()
a #)
Int#
_ -> st -> Res# st e ()
forall (st :: ZeroBitType) e a. st -> Res# st e a
Fail# st
st
{-# inline byteString #-}
getPos :: ParserT st e Pos
getPos :: forall (st :: ZeroBitType) e. ParserT st e Pos
getPos = (ForeignPtrContents -> Addr# -> Addr# -> st -> Res# st e Pos)
-> ParserT st e Pos
forall (st :: ZeroBitType) e a.
(ForeignPtrContents -> Addr# -> Addr# -> st -> Res# st e a)
-> ParserT st e a
ParserT \ForeignPtrContents
fp Addr#
eob Addr#
s st
st -> st -> Pos -> Addr# -> Res# st e Pos
forall (st :: ZeroBitType) a e. st -> a -> Addr# -> Res# st e a
OK# st
st (Addr# -> Addr# -> Pos
addrToPos# Addr#
eob Addr#
s) Addr#
s
{-# inline getPos #-}
setPos :: Pos -> ParserT st e ()
setPos :: forall (st :: ZeroBitType) e. Pos -> ParserT st e ()
setPos Pos
s = (ForeignPtrContents -> Addr# -> Addr# -> st -> Res# st e ())
-> ParserT st e ()
forall (st :: ZeroBitType) e a.
(ForeignPtrContents -> Addr# -> Addr# -> st -> Res# st e a)
-> ParserT st e a
ParserT \ForeignPtrContents
fp Addr#
eob Addr#
_ st
st -> st -> () -> Addr# -> Res# st e ()
forall (st :: ZeroBitType) a e. st -> a -> Addr# -> Res# st e a
OK# st
st () (Addr# -> Pos -> Addr#
posToAddr# Addr#
eob Pos
s)
{-# inline setPos #-}
spanOf :: ParserT st e a -> ParserT st e Span
spanOf :: forall (st :: ZeroBitType) e a. ParserT st e a -> ParserT st e Span
spanOf (ParserT ForeignPtrContents -> Addr# -> Addr# -> st -> Res# st e a
f) = (ForeignPtrContents -> Addr# -> Addr# -> st -> Res# st e Span)
-> ParserT st e Span
forall (st :: ZeroBitType) e a.
(ForeignPtrContents -> Addr# -> Addr# -> st -> Res# st e a)
-> ParserT st e a
ParserT \ForeignPtrContents
fp Addr#
eob Addr#
s st
st -> case ForeignPtrContents -> Addr# -> Addr# -> st -> Res# st e a
f ForeignPtrContents
fp Addr#
eob Addr#
s st
st of
OK# st
st' a
a Addr#
s' -> st -> Span -> Addr# -> Res# st e Span
forall (st :: ZeroBitType) a e. st -> a -> Addr# -> Res# st e a
OK# st
st' (Pos -> Pos -> Span
Span (Addr# -> Addr# -> Pos
addrToPos# Addr#
eob Addr#
s) (Addr# -> Addr# -> Pos
addrToPos# Addr#
eob Addr#
s')) Addr#
s'
Res# st e a
x -> Res# st e a -> Res# st e Span
forall a b. a -> b
unsafeCoerce# Res# st e a
x
{-# inline spanOf #-}
withSpan :: ParserT st e a -> (a -> Span -> ParserT st e b) -> ParserT st e b
withSpan :: forall (st :: ZeroBitType) e a b.
ParserT st e a -> (a -> Span -> ParserT st e b) -> ParserT st e b
withSpan (ParserT ForeignPtrContents -> Addr# -> Addr# -> st -> Res# st e a
f) a -> Span -> ParserT st e b
g = (ForeignPtrContents -> Addr# -> Addr# -> st -> Res# st e b)
-> ParserT st e b
forall (st :: ZeroBitType) e a.
(ForeignPtrContents -> Addr# -> Addr# -> st -> Res# st e a)
-> ParserT st e a
ParserT \ForeignPtrContents
fp Addr#
eob Addr#
s st
st -> case ForeignPtrContents -> Addr# -> Addr# -> st -> Res# st e a
f ForeignPtrContents
fp Addr#
eob Addr#
s st
st of
OK# st
st' a
a Addr#
s' -> ParserT st e b
-> ForeignPtrContents -> Addr# -> Addr# -> st -> Res# st e b
forall (st :: ZeroBitType) e a.
ParserT st e a
-> ForeignPtrContents -> Addr# -> Addr# -> st -> Res# st e a
runParserT# (a -> Span -> ParserT st e b
g a
a (Pos -> Pos -> Span
Span (Addr# -> Addr# -> Pos
addrToPos# Addr#
eob Addr#
s) (Addr# -> Addr# -> Pos
addrToPos# Addr#
eob Addr#
s'))) ForeignPtrContents
fp Addr#
eob Addr#
s' st
st'
Res# st e a
x -> Res# st e a -> Res# st e b
forall a b. a -> b
unsafeCoerce# Res# st e a
x
{-# inline withSpan #-}
byteStringOf :: ParserT st e a -> ParserT st e B.ByteString
byteStringOf :: forall (st :: ZeroBitType) e a.
ParserT st e a -> ParserT st e ByteString
byteStringOf (ParserT ForeignPtrContents -> Addr# -> Addr# -> st -> Res# st e a
f) = (ForeignPtrContents
-> Addr# -> Addr# -> st -> Res# st e ByteString)
-> ParserT st e ByteString
forall (st :: ZeroBitType) e a.
(ForeignPtrContents -> Addr# -> Addr# -> st -> Res# st e a)
-> ParserT st e a
ParserT \ForeignPtrContents
fp Addr#
eob Addr#
s st
st -> case ForeignPtrContents -> Addr# -> Addr# -> st -> Res# st e a
f ForeignPtrContents
fp Addr#
eob Addr#
s st
st of
OK# st
st' a
a Addr#
s' -> st -> ByteString -> Addr# -> Res# st e ByteString
forall (st :: ZeroBitType) a e. st -> a -> Addr# -> Res# st e a
OK# st
st' (ForeignPtr Word8 -> Int -> Int -> ByteString
B.PS (Addr# -> ForeignPtrContents -> ForeignPtr Word8
forall a. Addr# -> ForeignPtrContents -> ForeignPtr a
ForeignPtr Addr#
s ForeignPtrContents
fp) Int
0 (Int# -> Int
I# (Addr# -> Addr# -> Int#
minusAddr# Addr#
s' Addr#
s))) Addr#
s'
Res# st e a
x -> Res# st e a -> Res# st e ByteString
forall a b. a -> b
unsafeCoerce# Res# st e a
x
{-# inline byteStringOf #-}
withByteString :: ParserT st e a -> (a -> B.ByteString -> ParserT st e b) -> ParserT st e b
withByteString :: forall (st :: ZeroBitType) e a b.
ParserT st e a
-> (a -> ByteString -> ParserT st e b) -> ParserT st e b
withByteString (ParserT ForeignPtrContents -> Addr# -> Addr# -> st -> Res# st e a
f) a -> ByteString -> ParserT st e b
g = (ForeignPtrContents -> Addr# -> Addr# -> st -> Res# st e b)
-> ParserT st e b
forall (st :: ZeroBitType) e a.
(ForeignPtrContents -> Addr# -> Addr# -> st -> Res# st e a)
-> ParserT st e a
ParserT \ForeignPtrContents
fp Addr#
eob Addr#
s st
st -> case ForeignPtrContents -> Addr# -> Addr# -> st -> Res# st e a
f ForeignPtrContents
fp Addr#
eob Addr#
s st
st of
OK# st
st' a
a Addr#
s' -> ParserT st e b
-> ForeignPtrContents -> Addr# -> Addr# -> st -> Res# st e b
forall (st :: ZeroBitType) e a.
ParserT st e a
-> ForeignPtrContents -> Addr# -> Addr# -> st -> Res# st e a
runParserT# (a -> ByteString -> ParserT st e b
g a
a (ForeignPtr Word8 -> Int -> Int -> ByteString
B.PS (Addr# -> ForeignPtrContents -> ForeignPtr Word8
forall a. Addr# -> ForeignPtrContents -> ForeignPtr a
ForeignPtr Addr#
s ForeignPtrContents
fp) Int
0 (Int# -> Int
I# (Addr# -> Addr# -> Int#
minusAddr# Addr#
s' Addr#
s)))) ForeignPtrContents
fp Addr#
eob Addr#
s' st
st'
Res# st e a
x -> Res# st e a -> Res# st e b
forall a b. a -> b
unsafeCoerce# Res# st e a
x
{-# inline withByteString #-}
inSpan :: Span -> ParserT st e a -> ParserT st e a
inSpan :: forall (st :: ZeroBitType) e a.
Span -> ParserT st e a -> ParserT st e a
inSpan (Span Pos
s Pos
eob) (ParserT ForeignPtrContents -> Addr# -> Addr# -> st -> Res# st e a
f) = (ForeignPtrContents -> Addr# -> Addr# -> st -> Res# st e a)
-> ParserT st e a
forall (st :: ZeroBitType) e a.
(ForeignPtrContents -> Addr# -> Addr# -> st -> Res# st e a)
-> ParserT st e a
ParserT \ForeignPtrContents
fp Addr#
eob' Addr#
s' st
st ->
case ForeignPtrContents -> Addr# -> Addr# -> st -> Res# st e a
f ForeignPtrContents
fp (Addr# -> Pos -> Addr#
posToAddr# Addr#
eob' Pos
eob) (Addr# -> Pos -> Addr#
posToAddr# Addr#
eob' Pos
s) st
st of
OK# st
st' a
a Addr#
_ -> st -> a -> Addr# -> Res# st e a
forall (st :: ZeroBitType) a e. st -> a -> Addr# -> Res# st e a
OK# st
st' a
a Addr#
s'
Res# st e a
x -> Res# st e a -> Res# st e a
forall a b. a -> b
unsafeCoerce# Res# st e a
x
{-# inline inSpan #-}
unsafeSpanToByteString :: Span -> ParserT st e B.ByteString
unsafeSpanToByteString :: forall (st :: ZeroBitType) e. Span -> ParserT st e ByteString
unsafeSpanToByteString (Span Pos
l Pos
r) =
ParserT st e ByteString -> ParserT st e ByteString
forall (st :: ZeroBitType) e a. ParserT st e a -> ParserT st e a
lookahead (Pos -> ParserT st e ()
forall (st :: ZeroBitType) e. Pos -> ParserT st e ()
setPos Pos
l ParserT st e ()
-> ParserT st e ByteString -> ParserT st e ByteString
forall a b. ParserT st e a -> ParserT st e b -> ParserT st e b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParserT st e () -> ParserT st e ByteString
forall (st :: ZeroBitType) e a.
ParserT st e a -> ParserT st e ByteString
byteStringOf (Pos -> ParserT st e ()
forall (st :: ZeroBitType) e. Pos -> ParserT st e ()
setPos Pos
r))
{-# inline unsafeSpanToByteString #-}
validPos :: B.ByteString -> Pos -> Bool
validPos :: ByteString -> Pos -> Bool
validPos ByteString
str Pos
pos =
let go :: ParserT st e Bool
go = do
Pos
start <- ParserT st e Pos
forall (st :: ZeroBitType) e. ParserT st e Pos
getPos
Bool -> ParserT st e Bool
forall a. a -> ParserT st e a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Pos
start Pos -> Pos -> Bool
forall a. Ord a => a -> a -> Bool
<= Pos
pos Bool -> Bool -> Bool
&& Pos
pos Pos -> Pos -> Bool
forall a. Ord a => a -> a -> Bool
<= Pos
endPos)
in case Parser Any Bool -> ByteString -> Result Any Bool
forall e a. Parser e a -> ByteString -> Result e a
runParser Parser Any Bool
forall {st :: ZeroBitType} {e}. ParserT st e Bool
go ByteString
str of
OK Bool
b ByteString
_ -> Bool
b
Result Any Bool
_ -> String -> Bool
forall a. HasCallStack => String -> a
error String
"FlatParse.Basic.validPos: got a non-OK result, impossible"
{-# inline validPos #-}
posLineCols :: B.ByteString -> [Pos] -> [(Int, Int)]
posLineCols :: ByteString -> [Pos] -> [(Int, Int)]
posLineCols ByteString
str [Pos]
poss =
let go :: t -> t -> [(a, Pos)] -> ParserT st e [(a, (t, t))]
go !t
line !t
col [] = [(a, (t, t))] -> ParserT st e [(a, (t, t))]
forall a. a -> ParserT st e a
forall (f :: * -> *) a. Applicative f => a -> f a
pure []
go t
line t
col ((a
i, Pos
pos):[(a, Pos)]
poss) = do
Pos
p <- ParserT st e Pos
forall (st :: ZeroBitType) e. ParserT st e Pos
getPos
if Pos
pos Pos -> Pos -> Bool
forall a. Eq a => a -> a -> Bool
== Pos
p then
((a
i, (t
line, t
col))(a, (t, t)) -> [(a, (t, t))] -> [(a, (t, t))]
forall a. a -> [a] -> [a]
:) ([(a, (t, t))] -> [(a, (t, t))])
-> ParserT st e [(a, (t, t))] -> ParserT st e [(a, (t, t))]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> t -> t -> [(a, Pos)] -> ParserT st e [(a, (t, t))]
go t
line t
col [(a, Pos)]
poss
else do
Char
c <- ParserT st e Char
forall (st :: ZeroBitType) e. ParserT st e Char
anyChar
if Char
'\n' Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
c then
t -> t -> [(a, Pos)] -> ParserT st e [(a, (t, t))]
go (t
line t -> t -> t
forall a. Num a => a -> a -> a
+ t
1) t
0 ((a
i, Pos
pos)(a, Pos) -> [(a, Pos)] -> [(a, Pos)]
forall a. a -> [a] -> [a]
:[(a, Pos)]
poss)
else
t -> t -> [(a, Pos)] -> ParserT st e [(a, (t, t))]
go t
line (t
col t -> t -> t
forall a. Num a => a -> a -> a
+ t
1) ((a
i, Pos
pos)(a, Pos) -> [(a, Pos)] -> [(a, Pos)]
forall a. a -> [a] -> [a]
:[(a, Pos)]
poss)
sorted :: [(Int, Pos)]
sorted :: [(Int, Pos)]
sorted = ((Int, Pos) -> (Int, Pos) -> Ordering)
-> [(Int, Pos)] -> [(Int, Pos)]
forall a. (a -> a -> Ordering) -> [a] -> [a]
sortBy (\(Int
_, Pos
i) (Int
_, Pos
j) -> Pos -> Pos -> Ordering
forall a. Ord a => a -> a -> Ordering
compare Pos
i Pos
j) ([Int] -> [Pos] -> [(Int, Pos)]
forall a b. [a] -> [b] -> [(a, b)]
zip [Int
0..] [Pos]
poss)
in case Parser Any [(Int, (Int, Int))]
-> ByteString -> Result Any [(Int, (Int, Int))]
forall e a. Parser e a -> ByteString -> Result e a
runParser (Int -> Int -> [(Int, Pos)] -> Parser Any [(Int, (Int, Int))]
forall {t} {t} {a} {st :: ZeroBitType} {e}.
(Num t, Num t) =>
t -> t -> [(a, Pos)] -> ParserT st e [(a, (t, t))]
go Int
0 Int
0 [(Int, Pos)]
sorted) ByteString
str of
OK [(Int, (Int, Int))]
res ByteString
_ -> (Int, (Int, Int)) -> (Int, Int)
forall a b. (a, b) -> b
snd ((Int, (Int, Int)) -> (Int, Int))
-> [(Int, (Int, Int))] -> [(Int, Int)]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ((Int, (Int, Int)) -> (Int, (Int, Int)) -> Ordering)
-> [(Int, (Int, Int))] -> [(Int, (Int, Int))]
forall a. (a -> a -> Ordering) -> [a] -> [a]
sortBy (((Int, (Int, Int)) -> Int)
-> (Int, (Int, Int)) -> (Int, (Int, Int)) -> Ordering
forall a b. Ord a => (b -> a) -> b -> b -> Ordering
comparing (Int, (Int, Int)) -> Int
forall a b. (a, b) -> a
fst) [(Int, (Int, Int))]
res
Result Any [(Int, (Int, Int))]
_ -> String -> [(Int, Int)]
forall a. HasCallStack => String -> a
error String
"FlatParse.Basic.posLineCols: invalid position"
mkPos :: B.ByteString -> (Int, Int) -> Pos
mkPos :: ByteString -> (Int, Int) -> Pos
mkPos ByteString
str (Int
line', Int
col') =
let go :: Int -> Int -> ParserT st e Pos
go Int
line Int
col | Int
line Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
line' Bool -> Bool -> Bool
&& Int
col Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
col' = ParserT st e Pos
forall (st :: ZeroBitType) e. ParserT st e Pos
getPos
go Int
line Int
col = (do
Char
c <- ParserT st e Char
forall (st :: ZeroBitType) e. ParserT st e Char
anyChar
if Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'\n' then Int -> Int -> ParserT st e Pos
go (Int
line Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1) Int
0
else Int -> Int -> ParserT st e Pos
go Int
line (Int
col Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1)) ParserT st e Pos -> ParserT st e Pos -> ParserT st e Pos
forall (st :: ZeroBitType) e a.
ParserT st e a -> ParserT st e a -> ParserT st e a
<|> String -> ParserT st e Pos
forall a. HasCallStack => String -> a
error String
"FlatParse.Basic.mkPos: invalid position"
in case Parser Any Pos -> ByteString -> Result Any Pos
forall e a. Parser e a -> ByteString -> Result e a
runParser (Int -> Int -> Parser Any Pos
forall {st :: ZeroBitType} {e}. Int -> Int -> ParserT st e Pos
go Int
0 Int
0) ByteString
str of
OK Pos
res ByteString
_ -> Pos
res
Result Any Pos
_ -> String -> Pos
forall a. HasCallStack => String -> a
error String
"FlatParse.Basic.mkPos: got a non-OK result, impossible"
linesUtf8 :: B.ByteString -> [String]
linesUtf8 :: ByteString -> [String]
linesUtf8 ByteString
str =
let go :: ParserT st e [String]
go = ([] [String] -> ParserT st e () -> ParserT st e [String]
forall a b. a -> ParserT st e b -> ParserT st e a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ ParserT st e ()
forall (st :: ZeroBitType) e. ParserT st e ()
eof) ParserT st e [String]
-> ParserT st e [String] -> ParserT st e [String]
forall (st :: ZeroBitType) e a.
ParserT st e a -> ParserT st e a -> ParserT st e a
<|> ((:) (String -> [String] -> [String])
-> ParserT st e String -> ParserT st e ([String] -> [String])
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParserT st e String
forall (st :: ZeroBitType) e. ParserT st e String
takeLine ParserT st e ([String] -> [String])
-> ParserT st e [String] -> ParserT st e [String]
forall a b.
ParserT st e (a -> b) -> ParserT st e a -> ParserT st e b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ParserT st e [String]
go)
in case Parser Any [String] -> ByteString -> Result Any [String]
forall e a. Parser e a -> ByteString -> Result e a
runParser Parser Any [String]
forall {st :: ZeroBitType} {e}. ParserT st e [String]
go ByteString
str of
OK [String]
ls ByteString
_ -> [String]
ls
Result Any [String]
_ -> String -> [String]
forall a. HasCallStack => String -> a
error String
"FlatParse.Basic.linesUtf8: invalid input"
isolateToNextNull :: ParserT st e a -> ParserT st e a
isolateToNextNull :: forall (st :: ZeroBitType) e a. ParserT st e a -> ParserT st e a
isolateToNextNull (ParserT ForeignPtrContents -> Addr# -> Addr# -> st -> Res# st e a
p) = (ForeignPtrContents -> Addr# -> Addr# -> st -> Res# st e a)
-> ParserT st e a
forall (st :: ZeroBitType) e a.
(ForeignPtrContents -> Addr# -> Addr# -> st -> Res# st e a)
-> ParserT st e a
ParserT \ForeignPtrContents
fp Addr#
eob Addr#
s st
st -> ForeignPtrContents -> Addr# -> Addr# -> st -> Addr# -> Res# st e a
go ForeignPtrContents
fp Addr#
eob Addr#
s st
st Addr#
s
where
goP :: ForeignPtrContents -> Addr# -> Addr# -> st -> Res# st e a
goP ForeignPtrContents
fp Addr#
sNull Addr#
s0 st
st =
case ForeignPtrContents -> Addr# -> Addr# -> st -> Res# st e a
p ForeignPtrContents
fp Addr#
sNull Addr#
s0 st
st of
OK# st
st' a
a Addr#
s' ->
case Addr# -> Addr# -> Int#
eqAddr# Addr#
s' Addr#
sNull of
Int#
1# ->
st -> a -> Addr# -> Res# st e a
forall (st :: ZeroBitType) a e. st -> a -> Addr# -> Res# st e a
OK# st
st' a
a (Addr#
sNull Addr# -> Int# -> Addr#
`plusAddr#` Int#
1#)
Int#
_ -> st -> Res# st e a
forall (st :: ZeroBitType) e a. st -> Res# st e a
Fail# st
st'
Res# st e a
x -> Res# st e a
x
go8 :: ForeignPtrContents -> Addr# -> Addr# -> st -> Addr# -> Res# st e a
go8 ForeignPtrContents
fp Addr#
eob Addr#
s0 st
st Addr#
s =
case Addr# -> Addr# -> Int#
eqAddr# Addr#
eob Addr#
s of
Int#
1# -> st -> Res# st e a
forall (st :: ZeroBitType) e a. st -> Res# st e a
Fail# st
st
Int#
_ ->
let s' :: Addr#
s' = Addr#
s Addr# -> Int# -> Addr#
`plusAddr#` Int#
1# in
#if MIN_VERSION_base(4,16,0)
case Word8# -> Word8# -> Int#
eqWord8# (Addr# -> Int# -> Word8#
indexWord8OffAddr# Addr#
s Int#
0#) (Word# -> Word8#
wordToWord8# Word#
0##) of
#else
case eqWord# (indexWord8OffAddr# s 0#) 0## of
#endif
Int#
1# -> ForeignPtrContents -> Addr# -> Addr# -> st -> Res# st e a
goP ForeignPtrContents
fp Addr#
s Addr#
s0 st
st
Int#
_ -> ForeignPtrContents -> Addr# -> Addr# -> st -> Addr# -> Res# st e a
go8 ForeignPtrContents
fp Addr#
eob Addr#
s0 st
st Addr#
s'
go :: ForeignPtrContents -> Addr# -> Addr# -> st -> Addr# -> Res# st e a
go ForeignPtrContents
fp Addr#
eob Addr#
s0 st
st Addr#
s =
let sWord :: Addr#
sWord = Addr#
s Addr# -> Int# -> Addr#
`plusAddr#` Int#
8# in
case Addr# -> Addr# -> Int#
gtAddr# Addr#
sWord Addr#
eob of
Int#
1# ->
ForeignPtrContents -> Addr# -> Addr# -> st -> Addr# -> Res# st e a
go8 ForeignPtrContents
fp Addr#
eob Addr#
s0 st
st Addr#
s
Int#
_ ->
#if defined(WORDS_BIGENDIAN)
let !x@(I# x#) = Common.zbytel'intermediate (I# (indexIntOffAddr# s 0#)) in
#else
let !x :: Int
x@(I# Int#
x#) = Int -> Int
forall a. (FiniteBits a, Num a) => a -> a
Common.zbyter'intermediate (Int# -> Int
I# (Addr# -> Int# -> Int#
indexIntOffAddr# Addr#
s Int#
0#)) in
#endif
case Int#
x# Int# -> Int# -> Int#
==# Int#
0# of
Int#
1# -> ForeignPtrContents -> Addr# -> Addr# -> st -> Addr# -> Res# st e a
go ForeignPtrContents
fp Addr#
eob Addr#
s0 st
st Addr#
sWord
Int#
_ ->
#if defined(WORDS_BIGENDIAN)
let !(I# nullIdx#) = Common.zbytel'toIdx x in
#else
let !(I# Int#
nullIdx#) = Int -> Int
forall a. (FiniteBits a, Num a) => a -> Int
Common.zbyter'toIdx Int
x in
#endif
let sNull :: Addr#
sNull = Addr#
s Addr# -> Int# -> Addr#
`plusAddr#` Int#
nullIdx# in
ForeignPtrContents -> Addr# -> Addr# -> st -> Res# st e a
goP ForeignPtrContents
fp Addr#
sNull Addr#
s0 st
st
{-# inline isolateToNextNull #-}
anyCString :: ParserT st e B.ByteString
anyCString :: forall (st :: ZeroBitType) e. ParserT st e ByteString
anyCString = ParserT st e ByteString -> ParserT st e ByteString
forall (st :: ZeroBitType) e a. ParserT st e a -> ParserT st e a
isolateToNextNull ParserT st e ByteString
forall (st :: ZeroBitType) e. ParserT st e ByteString
takeRest
{-# inline anyCString #-}
anyCStringUnsafe :: ParserT st e B.ByteString
{-# inline anyCStringUnsafe #-}
#if MIN_VERSION_base(4,15,0)
anyCStringUnsafe :: forall (st :: ZeroBitType) e. ParserT st e ByteString
anyCStringUnsafe = (ForeignPtrContents
-> Addr# -> Addr# -> st -> Res# st e ByteString)
-> ParserT st e ByteString
forall (st :: ZeroBitType) e a.
(ForeignPtrContents -> Addr# -> Addr# -> st -> Res# st e a)
-> ParserT st e a
ParserT \ForeignPtrContents
fp Addr#
eob Addr#
s st
st ->
case Addr# -> Addr# -> Int#
eqAddr# Addr#
eob Addr#
s of
Int#
1# -> st -> Res# st e ByteString
forall (st :: ZeroBitType) e a. st -> Res# st e a
Fail# st
st
Int#
_ -> let n# :: Int#
n# = Addr# -> Int#
cstringLength# Addr#
s
s'# :: Addr#
s'# = Addr# -> Int# -> Addr#
plusAddr# Addr#
s (Int#
n# Int# -> Int# -> Int#
+# Int#
1#)
in st -> ByteString -> Addr# -> Res# st e ByteString
forall (st :: ZeroBitType) a e. st -> a -> Addr# -> Res# st e a
OK# st
st (ForeignPtr Word8 -> Int -> Int -> ByteString
B.PS (Addr# -> ForeignPtrContents -> ForeignPtr Word8
forall a. Addr# -> ForeignPtrContents -> ForeignPtr a
ForeignPtr Addr#
s ForeignPtrContents
fp) Int
0 (Int# -> Int
I# Int#
n#)) Addr#
s'#
#else
anyCStringUnsafe = error "Flatparse.Basic.anyCStringUnsafe: requires GHC 9.0 / base-4.15, not available on this compiler"
#endif
anyVarintProtobuf :: ParserT st e Int
anyVarintProtobuf :: forall (st :: ZeroBitType) e. ParserT st e Int
anyVarintProtobuf = (ForeignPtrContents -> Addr# -> Addr# -> st -> Res# st e Int)
-> ParserT st e Int
forall (st :: ZeroBitType) e a.
(ForeignPtrContents -> Addr# -> Addr# -> st -> Res# st e a)
-> ParserT st e a
ParserT \ForeignPtrContents
fp Addr#
eob Addr#
s st
st ->
case Addr# -> Addr# -> (# (# #) | (# Int#, Addr#, Int# #) #)
Common.anyVarintProtobuf# Addr#
eob Addr#
s of
(# (##) | #) -> st -> Res# st e Int
forall (st :: ZeroBitType) e a. st -> Res# st e a
Fail# st
st
(# | (# Int#
w#, Addr#
s#, Int#
bits# #) #) ->
case Int#
bits# Int# -> Int# -> Int#
># Int#
63# of
Int#
0# -> st -> Int -> Addr# -> Res# st e Int
forall (st :: ZeroBitType) a e. st -> a -> Addr# -> Res# st e a
OK# st
st (Int# -> Int
I# Int#
w#) Addr#
s#
Int#
_ -> st -> Res# st e Int
forall (st :: ZeroBitType) e a. st -> Res# st e a
Fail# st
st
{-# inline anyVarintProtobuf #-}