{-# language BangPatterns #-}
{-# language BinaryLiterals #-}
{-# language DataKinds #-}
{-# language DeriveFunctor #-}
{-# language DerivingStrategies #-}
{-# language GADTSyntax #-}
{-# language KindSignatures #-}
{-# language LambdaCase #-}
{-# language MagicHash #-}
{-# language MultiWayIf #-}
{-# language PolyKinds #-}
{-# language RankNTypes #-}
{-# language ScopedTypeVariables #-}
{-# language StandaloneDeriving #-}
{-# language TypeApplications #-}
{-# language UnboxedSums #-}
{-# language UnboxedTuples #-}
{-# language CPP #-}

-- | Parse input as though it were text encoded by
-- ISO 8859-1 (Latin-1). All byte sequences are valid
-- text under ISO 8859-1.
module Data.Bytes.Parser.Latin
  ( -- * Matching
    -- ** Required
    char
  , char2
  , char3
  , char4
  , char5
  , char6
  , char7
  , char8
  , char9
  , char10
  , char11
  , char12
    -- ** Try
  , trySatisfy
  , trySatisfyThen
    -- * One Character
  , any
  , opt
  , opt#
    -- * Many Characters
  , takeTrailedBy
    -- * Lookahead
  , peek
  , peek'
    -- * Skip
  , skipDigits
  , skipDigits1
  , skipChar
  , skipChar1
  , skipTrailedBy
  , skipUntil
  , skipWhile
    -- * End of Input
  , endOfInput
  , isEndOfInput
    -- * Numbers
    -- ** Decimal
    -- *** Unsigned
  , decWord
  , decWord8
  , decWord16
  , decWord32
  , decWord64
    -- *** Signed
  , decUnsignedInt
  , decUnsignedInt#
  , decSignedInt
  , decStandardInt
  , decTrailingInt
  , decTrailingInt#
  , decSignedInteger
  , decUnsignedInteger
  , decTrailingInteger
    -- ** Hexadecimal
    -- *** Variable Length
  , hexWord8
  , hexWord16
    -- *** Fixed Length
  , hexFixedWord8
  , hexFixedWord16
  , hexFixedWord32
  , hexFixedWord64
    -- *** Digit
  , hexNibbleLower
  , tryHexNibbleLower
  , hexNibble
  , tryHexNibble
  ) where

import Prelude hiding (length,any,fail,takeWhile)

import Data.Bits ((.|.))
import Data.Bytes.Types (Bytes(..))
import Data.Bytes.Parser.Internal (InternalStep(..),unfailing)
import Data.Bytes.Parser.Internal (Parser(..),ST#,uneffectful,Result#,uneffectful#)
import Data.Bytes.Parser.Internal (Result(..),indexLatinCharArray,upcastUnitSuccess)
import Data.Bytes.Parser.Internal (boxBytes)
import Data.Bytes.Parser (bindFromLiftedToInt,isEndOfInput,endOfInput)
import Data.Bytes.Parser.Unsafe (expose,cursor,unconsume)
import Data.Word (Word8)
import Data.Char (ord)
import Data.Kind (Type)
import GHC.Exts (Int(I#),Char(C#),Word#,Int#,Char#,(+#),(-#),indexCharArray#)
import GHC.Exts (TYPE,RuntimeRep,int2Word#,or#)
import GHC.Exts (ltWord#,gtWord#,notI#)
import GHC.Word (Word(W#),Word8(W8#),Word16(W16#),Word32(W32#),Word64(W64#))

import qualified GHC.Exts as Exts
import qualified Data.Bytes as Bytes
import qualified Data.Primitive as PM

-- | Runs the predicate on the next character in the input. If the
-- predicate is matched, this consumes the character. Otherwise,
-- the character is not consumed. This returns @False@ if the end
-- of the input has been reached. This never fails.
trySatisfy :: (Char -> Bool) -> Parser e s Bool
trySatisfy :: (Char -> Bool) -> Parser e s Bool
trySatisfy Char -> Bool
f = (Bytes -> Result e Bool) -> Parser e s Bool
forall e a s. (Bytes -> Result e a) -> Parser e s a
uneffectful ((Bytes -> Result e Bool) -> Parser e s Bool)
-> (Bytes -> Result e Bool) -> Parser e s Bool
forall a b. (a -> b) -> a -> b
$ \Bytes
chunk -> case Bytes -> Int
length Bytes
chunk of
  Int
0 -> Bool -> Int -> Int -> Result e Bool
forall e a. a -> Int -> Int -> Result e a
Success Bool
False (Bytes -> Int
offset Bytes
chunk) (Bytes -> Int
length Bytes
chunk)
  Int
_ -> case Char -> Bool
f (ByteArray -> Int -> Char
indexLatinCharArray (Bytes -> ByteArray
array Bytes
chunk) (Bytes -> Int
offset Bytes
chunk)) of
    Bool
True -> Bool -> Int -> Int -> Result e Bool
forall e a. a -> Int -> Int -> Result e a
Success Bool
True (Bytes -> Int
offset Bytes
chunk Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1) (Bytes -> Int
length Bytes
chunk Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1)
    Bool
False -> Bool -> Int -> Int -> Result e Bool
forall e a. a -> Int -> Int -> Result e a
Success Bool
False (Bytes -> Int
offset Bytes
chunk) (Bytes -> Int
length Bytes
chunk)

-- | Runs the function on the next character in the input. If the
-- function returns @Just@, this consumes the character and then
-- runs the parser on the remaining input. If the function returns
-- @Nothing@, this does not consume the tested character, and it
-- runs the default parser on the input (which includes the tested
-- character). If there is no input remaining, this also runs the
-- default parser. This combinator never fails.
trySatisfyThen :: forall (r :: RuntimeRep) (e :: Type) (s :: Type) (a :: TYPE r).
     Parser e s a -- ^ Default parser. Runs on @Nothing@ or end of input.
  -> (Char -> Maybe (Parser e s a)) -- ^ Parser-selecting predicate
  -> Parser e s a
{-# inline trySatisfyThen #-}
trySatisfyThen :: Parser e s a -> (Char -> Maybe (Parser e s a)) -> Parser e s a
trySatisfyThen (Parser (# ByteArray#, Int#, Int# #) -> ST# s (Result# e a)
g) Char -> Maybe (Parser e s a)
f = ((# ByteArray#, Int#, Int# #) -> ST# s (Result# e a))
-> Parser e s a
forall e s a.
((# ByteArray#, Int#, Int# #) -> ST# s (Result# e a))
-> Parser e s a
Parser
  (\input :: (# ByteArray#, Int#, Int# #)
input@(# ByteArray#
arr,Int#
off0,Int#
len0 #) State# s
s0 -> case Int#
len0 of
    Int#
0# -> (# ByteArray#, Int#, Int# #) -> ST# s (Result# e a)
g (# ByteArray#, Int#, Int# #)
input State# s
s0
    Int#
_ -> case Char -> Maybe (Parser e s a)
f (Char# -> Char
C# (ByteArray# -> Int# -> Char#
indexCharArray# ByteArray#
arr Int#
off0)) of
      Maybe (Parser e s a)
Nothing -> (# ByteArray#, Int#, Int# #) -> ST# s (Result# e a)
g (# ByteArray#, Int#, Int# #)
input State# s
s0
      Just (Parser (# ByteArray#, Int#, Int# #) -> ST# s (Result# e a)
p) -> (# ByteArray#, Int#, Int# #) -> ST# s (Result# e a)
p (# ByteArray#
arr, Int#
off0 Int# -> Int# -> Int#
+# Int#
1#, Int#
len0 Int# -> Int# -> Int#
-# Int#
1# #) State# s
s0
  )

-- | Consume the next character, failing if it does not
-- match the expected value or if there is no more input.
char :: e -> Char -> Parser e s ()
{-# inline char #-}
char :: e -> Char -> Parser e s ()
char e
e !Char
c = (Bytes -> Result e ()) -> Parser e s ()
forall e a s. (Bytes -> Result e a) -> Parser e s a
uneffectful ((Bytes -> Result e ()) -> Parser e s ())
-> (Bytes -> Result e ()) -> Parser e s ()
forall a b. (a -> b) -> a -> b
$ \Bytes
chunk -> if Bytes -> Int
length Bytes
chunk Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
0
  then if ByteArray -> Int -> Char
indexLatinCharArray (Bytes -> ByteArray
array Bytes
chunk) (Bytes -> Int
offset Bytes
chunk) Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
c
    then () -> Int -> Int -> Result e ()
forall e a. a -> Int -> Int -> Result e a
Success () (Bytes -> Int
offset Bytes
chunk Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1) (Bytes -> Int
length Bytes
chunk Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1)
    else e -> Result e ()
forall e a. e -> Result e a
Failure e
e
  else e -> Result e ()
forall e a. e -> Result e a
Failure e
e

-- | Consume the next two characters, failing if they do
-- not match the expected values.
--
-- > char2 e a b === char e a *> char e b
char2 :: e -> Char -> Char -> Parser e s ()
{-# inline char2 #-}
char2 :: e -> Char -> Char -> Parser e s ()
char2 e
e !Char
c0 !Char
c1 = (Bytes -> Result e ()) -> Parser e s ()
forall e a s. (Bytes -> Result e a) -> Parser e s a
uneffectful ((Bytes -> Result e ()) -> Parser e s ())
-> (Bytes -> Result e ()) -> Parser e s ()
forall a b. (a -> b) -> a -> b
$ \Bytes
chunk ->
  if | Bytes -> Int
length Bytes
chunk Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
1
     , ByteArray -> Int -> Char
indexLatinCharArray (Bytes -> ByteArray
array Bytes
chunk) (Bytes -> Int
offset Bytes
chunk) Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
c0
     , ByteArray -> Int -> Char
indexLatinCharArray (Bytes -> ByteArray
array Bytes
chunk) (Bytes -> Int
offset Bytes
chunk Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1) Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
c1
         -> () -> Int -> Int -> Result e ()
forall e a. a -> Int -> Int -> Result e a
Success () (Bytes -> Int
offset Bytes
chunk Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
2) (Bytes -> Int
length Bytes
chunk Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
2)
     | Bool
otherwise -> e -> Result e ()
forall e a. e -> Result e a
Failure e
e

-- | Consume three characters, failing if they do
-- not match the expected values.
--
-- > char3 e a b c === char e a *> char e b *> char e c
char3 :: e -> Char -> Char -> Char -> Parser e s ()
{-# inline char3 #-}
char3 :: e -> Char -> Char -> Char -> Parser e s ()
char3 e
e !Char
c0 !Char
c1 !Char
c2 = (Bytes -> Result e ()) -> Parser e s ()
forall e a s. (Bytes -> Result e a) -> Parser e s a
uneffectful ((Bytes -> Result e ()) -> Parser e s ())
-> (Bytes -> Result e ()) -> Parser e s ()
forall a b. (a -> b) -> a -> b
$ \Bytes
chunk ->
  if | Bytes -> Int
length Bytes
chunk Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
2
     , ByteArray -> Int -> Char
indexLatinCharArray (Bytes -> ByteArray
array Bytes
chunk) (Bytes -> Int
offset Bytes
chunk) Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
c0
     , ByteArray -> Int -> Char
indexLatinCharArray (Bytes -> ByteArray
array Bytes
chunk) (Bytes -> Int
offset Bytes
chunk Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1) Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
c1
     , ByteArray -> Int -> Char
indexLatinCharArray (Bytes -> ByteArray
array Bytes
chunk) (Bytes -> Int
offset Bytes
chunk Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
2) Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
c2
         -> () -> Int -> Int -> Result e ()
forall e a. a -> Int -> Int -> Result e a
Success () (Bytes -> Int
offset Bytes
chunk Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
3) (Bytes -> Int
length Bytes
chunk Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
3)
     | Bool
otherwise -> e -> Result e ()
forall e a. e -> Result e a
Failure e
e

-- | Consume four characters, failing if they do
-- not match the expected values.
--
-- > char4 e a b c d === char e a *> char e b *> char e c *> char e d
char4 :: e -> Char -> Char -> Char -> Char -> Parser e s ()
{-# inline char4 #-}
char4 :: e -> Char -> Char -> Char -> Char -> Parser e s ()
char4 e
e !Char
c0 !Char
c1 !Char
c2 !Char
c3 = (Bytes -> Result e ()) -> Parser e s ()
forall e a s. (Bytes -> Result e a) -> Parser e s a
uneffectful ((Bytes -> Result e ()) -> Parser e s ())
-> (Bytes -> Result e ()) -> Parser e s ()
forall a b. (a -> b) -> a -> b
$ \Bytes
chunk ->
  if | Bytes -> Int
length Bytes
chunk Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
3
     , ByteArray -> Int -> Char
indexLatinCharArray (Bytes -> ByteArray
array Bytes
chunk) (Bytes -> Int
offset Bytes
chunk) Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
c0
     , ByteArray -> Int -> Char
indexLatinCharArray (Bytes -> ByteArray
array Bytes
chunk) (Bytes -> Int
offset Bytes
chunk Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1) Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
c1
     , ByteArray -> Int -> Char
indexLatinCharArray (Bytes -> ByteArray
array Bytes
chunk) (Bytes -> Int
offset Bytes
chunk Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
2) Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
c2
     , ByteArray -> Int -> Char
indexLatinCharArray (Bytes -> ByteArray
array Bytes
chunk) (Bytes -> Int
offset Bytes
chunk Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
3) Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
c3
         -> () -> Int -> Int -> Result e ()
forall e a. a -> Int -> Int -> Result e a
Success () (Bytes -> Int
offset Bytes
chunk Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
4) (Bytes -> Int
length Bytes
chunk Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
4)
     | Bool
otherwise -> e -> Result e ()
forall e a. e -> Result e a
Failure e
e

-- | Consume five characters, failing if they do
-- not match the expected values.
char5 :: e -> Char -> Char -> Char -> Char -> Char -> Parser e s ()
{-# inline char5 #-}
char5 :: e -> Char -> Char -> Char -> Char -> Char -> Parser e s ()
char5 e
e !Char
c0 !Char
c1 !Char
c2 !Char
c3 !Char
c4 = (Bytes -> Result e ()) -> Parser e s ()
forall e a s. (Bytes -> Result e a) -> Parser e s a
uneffectful ((Bytes -> Result e ()) -> Parser e s ())
-> (Bytes -> Result e ()) -> Parser e s ()
forall a b. (a -> b) -> a -> b
$ \Bytes
chunk ->
  if | Bytes -> Int
length Bytes
chunk Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
4
     , ByteArray -> Int -> Char
indexLatinCharArray (Bytes -> ByteArray
array Bytes
chunk) (Bytes -> Int
offset Bytes
chunk) Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
c0
     , ByteArray -> Int -> Char
indexLatinCharArray (Bytes -> ByteArray
array Bytes
chunk) (Bytes -> Int
offset Bytes
chunk Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1) Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
c1
     , ByteArray -> Int -> Char
indexLatinCharArray (Bytes -> ByteArray
array Bytes
chunk) (Bytes -> Int
offset Bytes
chunk Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
2) Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
c2
     , ByteArray -> Int -> Char
indexLatinCharArray (Bytes -> ByteArray
array Bytes
chunk) (Bytes -> Int
offset Bytes
chunk Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
3) Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
c3
     , ByteArray -> Int -> Char
indexLatinCharArray (Bytes -> ByteArray
array Bytes
chunk) (Bytes -> Int
offset Bytes
chunk Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
4) Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
c4
         -> () -> Int -> Int -> Result e ()
forall e a. a -> Int -> Int -> Result e a
Success () (Bytes -> Int
offset Bytes
chunk Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
5) (Bytes -> Int
length Bytes
chunk Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
5)
     | Bool
otherwise -> e -> Result e ()
forall e a. e -> Result e a
Failure e
e

-- | Consume six characters, failing if they do
-- not match the expected values.
char6 :: e -> Char -> Char -> Char -> Char -> Char -> Char -> Parser e s ()
{-# inline char6 #-}
char6 :: e -> Char -> Char -> Char -> Char -> Char -> Char -> Parser e s ()
char6 e
e !Char
c0 !Char
c1 !Char
c2 !Char
c3 !Char
c4 !Char
c5 = (Bytes -> Result e ()) -> Parser e s ()
forall e a s. (Bytes -> Result e a) -> Parser e s a
uneffectful ((Bytes -> Result e ()) -> Parser e s ())
-> (Bytes -> Result e ()) -> Parser e s ()
forall a b. (a -> b) -> a -> b
$ \Bytes
chunk ->
  if | Bytes -> Int
length Bytes
chunk Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
5
     , ByteArray -> Int -> Char
indexLatinCharArray (Bytes -> ByteArray
array Bytes
chunk) (Bytes -> Int
offset Bytes
chunk) Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
c0
     , ByteArray -> Int -> Char
indexLatinCharArray (Bytes -> ByteArray
array Bytes
chunk) (Bytes -> Int
offset Bytes
chunk Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1) Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
c1
     , ByteArray -> Int -> Char
indexLatinCharArray (Bytes -> ByteArray
array Bytes
chunk) (Bytes -> Int
offset Bytes
chunk Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
2) Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
c2
     , ByteArray -> Int -> Char
indexLatinCharArray (Bytes -> ByteArray
array Bytes
chunk) (Bytes -> Int
offset Bytes
chunk Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
3) Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
c3
     , ByteArray -> Int -> Char
indexLatinCharArray (Bytes -> ByteArray
array Bytes
chunk) (Bytes -> Int
offset Bytes
chunk Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
4) Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
c4
     , ByteArray -> Int -> Char
indexLatinCharArray (Bytes -> ByteArray
array Bytes
chunk) (Bytes -> Int
offset Bytes
chunk Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
5) Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
c5
         -> () -> Int -> Int -> Result e ()
forall e a. a -> Int -> Int -> Result e a
Success () (Bytes -> Int
offset Bytes
chunk Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
6) (Bytes -> Int
length Bytes
chunk Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
6)
     | Bool
otherwise -> e -> Result e ()
forall e a. e -> Result e a
Failure e
e

-- | Consume seven characters, failing if they do
-- not match the expected values.
char7 :: e -> Char -> Char -> Char -> Char -> Char -> Char -> Char -> Parser e s ()
{-# inline char7 #-}
char7 :: e
-> Char
-> Char
-> Char
-> Char
-> Char
-> Char
-> Char
-> Parser e s ()
char7 e
e !Char
c0 !Char
c1 !Char
c2 !Char
c3 !Char
c4 !Char
c5 !Char
c6 = (Bytes -> Result e ()) -> Parser e s ()
forall e a s. (Bytes -> Result e a) -> Parser e s a
uneffectful ((Bytes -> Result e ()) -> Parser e s ())
-> (Bytes -> Result e ()) -> Parser e s ()
forall a b. (a -> b) -> a -> b
$ \Bytes
chunk ->
  if | Bytes -> Int
length Bytes
chunk Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
6
     , ByteArray -> Int -> Char
indexLatinCharArray (Bytes -> ByteArray
array Bytes
chunk) (Bytes -> Int
offset Bytes
chunk) Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
c0
     , ByteArray -> Int -> Char
indexLatinCharArray (Bytes -> ByteArray
array Bytes
chunk) (Bytes -> Int
offset Bytes
chunk Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1) Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
c1
     , ByteArray -> Int -> Char
indexLatinCharArray (Bytes -> ByteArray
array Bytes
chunk) (Bytes -> Int
offset Bytes
chunk Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
2) Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
c2
     , ByteArray -> Int -> Char
indexLatinCharArray (Bytes -> ByteArray
array Bytes
chunk) (Bytes -> Int
offset Bytes
chunk Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
3) Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
c3
     , ByteArray -> Int -> Char
indexLatinCharArray (Bytes -> ByteArray
array Bytes
chunk) (Bytes -> Int
offset Bytes
chunk Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
4) Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
c4
     , ByteArray -> Int -> Char
indexLatinCharArray (Bytes -> ByteArray
array Bytes
chunk) (Bytes -> Int
offset Bytes
chunk Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
5) Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
c5
     , ByteArray -> Int -> Char
indexLatinCharArray (Bytes -> ByteArray
array Bytes
chunk) (Bytes -> Int
offset Bytes
chunk Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
6) Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
c6
         -> () -> Int -> Int -> Result e ()
forall e a. a -> Int -> Int -> Result e a
Success () (Bytes -> Int
offset Bytes
chunk Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
7) (Bytes -> Int
length Bytes
chunk Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
7)
     | Bool
otherwise -> e -> Result e ()
forall e a. e -> Result e a
Failure e
e

-- | Consume eight characters, failing if they do
-- not match the expected values.
char8 :: e -> Char -> Char -> Char -> Char -> Char -> Char -> Char -> Char -> Parser e s ()
{-# inline char8 #-}
char8 :: e
-> Char
-> Char
-> Char
-> Char
-> Char
-> Char
-> Char
-> Char
-> Parser e s ()
char8 e
e !Char
c0 !Char
c1 !Char
c2 !Char
c3 !Char
c4 !Char
c5 !Char
c6 !Char
c7 = (Bytes -> Result e ()) -> Parser e s ()
forall e a s. (Bytes -> Result e a) -> Parser e s a
uneffectful ((Bytes -> Result e ()) -> Parser e s ())
-> (Bytes -> Result e ()) -> Parser e s ()
forall a b. (a -> b) -> a -> b
$ \Bytes
chunk ->
  if | Bytes -> Int
length Bytes
chunk Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
7
     , ByteArray -> Int -> Char
indexLatinCharArray (Bytes -> ByteArray
array Bytes
chunk) (Bytes -> Int
offset Bytes
chunk) Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
c0
     , ByteArray -> Int -> Char
indexLatinCharArray (Bytes -> ByteArray
array Bytes
chunk) (Bytes -> Int
offset Bytes
chunk Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1) Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
c1
     , ByteArray -> Int -> Char
indexLatinCharArray (Bytes -> ByteArray
array Bytes
chunk) (Bytes -> Int
offset Bytes
chunk Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
2) Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
c2
     , ByteArray -> Int -> Char
indexLatinCharArray (Bytes -> ByteArray
array Bytes
chunk) (Bytes -> Int
offset Bytes
chunk Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
3) Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
c3
     , ByteArray -> Int -> Char
indexLatinCharArray (Bytes -> ByteArray
array Bytes
chunk) (Bytes -> Int
offset Bytes
chunk Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
4) Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
c4
     , ByteArray -> Int -> Char
indexLatinCharArray (Bytes -> ByteArray
array Bytes
chunk) (Bytes -> Int
offset Bytes
chunk Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
5) Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
c5
     , ByteArray -> Int -> Char
indexLatinCharArray (Bytes -> ByteArray
array Bytes
chunk) (Bytes -> Int
offset Bytes
chunk Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
6) Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
c6
     , ByteArray -> Int -> Char
indexLatinCharArray (Bytes -> ByteArray
array Bytes
chunk) (Bytes -> Int
offset Bytes
chunk Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
7) Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
c7
         -> () -> Int -> Int -> Result e ()
forall e a. a -> Int -> Int -> Result e a
Success () (Bytes -> Int
offset Bytes
chunk Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
8) (Bytes -> Int
length Bytes
chunk Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
8)
     | Bool
otherwise -> e -> Result e ()
forall e a. e -> Result e a
Failure e
e

-- | Consume nine characters, failing if they do
-- not match the expected values.
char9 :: e -> Char -> Char -> Char -> Char
  -> Char -> Char -> Char -> Char -> Char -> Parser e s ()
{-# inline char9 #-}
char9 :: e
-> Char
-> Char
-> Char
-> Char
-> Char
-> Char
-> Char
-> Char
-> Char
-> Parser e s ()
char9 e
e !Char
c0 !Char
c1 !Char
c2 !Char
c3 !Char
c4 !Char
c5 !Char
c6 !Char
c7 !Char
c8 = (Bytes -> Result e ()) -> Parser e s ()
forall e a s. (Bytes -> Result e a) -> Parser e s a
uneffectful ((Bytes -> Result e ()) -> Parser e s ())
-> (Bytes -> Result e ()) -> Parser e s ()
forall a b. (a -> b) -> a -> b
$ \Bytes
chunk ->
  if | Bytes -> Int
length Bytes
chunk Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
8
     , ByteArray -> Int -> Char
indexLatinCharArray (Bytes -> ByteArray
array Bytes
chunk) (Bytes -> Int
offset Bytes
chunk) Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
c0
     , ByteArray -> Int -> Char
indexLatinCharArray (Bytes -> ByteArray
array Bytes
chunk) (Bytes -> Int
offset Bytes
chunk Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1) Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
c1
     , ByteArray -> Int -> Char
indexLatinCharArray (Bytes -> ByteArray
array Bytes
chunk) (Bytes -> Int
offset Bytes
chunk Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
2) Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
c2
     , ByteArray -> Int -> Char
indexLatinCharArray (Bytes -> ByteArray
array Bytes
chunk) (Bytes -> Int
offset Bytes
chunk Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
3) Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
c3
     , ByteArray -> Int -> Char
indexLatinCharArray (Bytes -> ByteArray
array Bytes
chunk) (Bytes -> Int
offset Bytes
chunk Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
4) Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
c4
     , ByteArray -> Int -> Char
indexLatinCharArray (Bytes -> ByteArray
array Bytes
chunk) (Bytes -> Int
offset Bytes
chunk Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
5) Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
c5
     , ByteArray -> Int -> Char
indexLatinCharArray (Bytes -> ByteArray
array Bytes
chunk) (Bytes -> Int
offset Bytes
chunk Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
6) Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
c6
     , ByteArray -> Int -> Char
indexLatinCharArray (Bytes -> ByteArray
array Bytes
chunk) (Bytes -> Int
offset Bytes
chunk Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
7) Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
c7
     , ByteArray -> Int -> Char
indexLatinCharArray (Bytes -> ByteArray
array Bytes
chunk) (Bytes -> Int
offset Bytes
chunk Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
8) Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
c8
         -> () -> Int -> Int -> Result e ()
forall e a. a -> Int -> Int -> Result e a
Success () (Bytes -> Int
offset Bytes
chunk Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
9) (Bytes -> Int
length Bytes
chunk Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
9)
     | Bool
otherwise -> e -> Result e ()
forall e a. e -> Result e a
Failure e
e

-- | Consume ten characters, failing if they do
-- not match the expected values.
char10 :: e -> Char -> Char -> Char -> Char -> Char
  -> Char -> Char -> Char -> Char -> Char -> Parser e s ()
{-# inline char10 #-}
char10 :: e
-> Char
-> Char
-> Char
-> Char
-> Char
-> Char
-> Char
-> Char
-> Char
-> Char
-> Parser e s ()
char10 e
e !Char
c0 !Char
c1 !Char
c2 !Char
c3 !Char
c4 !Char
c5 !Char
c6 !Char
c7 !Char
c8 !Char
c9 = (Bytes -> Result e ()) -> Parser e s ()
forall e a s. (Bytes -> Result e a) -> Parser e s a
uneffectful ((Bytes -> Result e ()) -> Parser e s ())
-> (Bytes -> Result e ()) -> Parser e s ()
forall a b. (a -> b) -> a -> b
$ \Bytes
chunk ->
  if | Bytes -> Int
length Bytes
chunk Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
9
     , ByteArray -> Int -> Char
indexLatinCharArray (Bytes -> ByteArray
array Bytes
chunk) (Bytes -> Int
offset Bytes
chunk) Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
c0
     , ByteArray -> Int -> Char
indexLatinCharArray (Bytes -> ByteArray
array Bytes
chunk) (Bytes -> Int
offset Bytes
chunk Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1) Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
c1
     , ByteArray -> Int -> Char
indexLatinCharArray (Bytes -> ByteArray
array Bytes
chunk) (Bytes -> Int
offset Bytes
chunk Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
2) Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
c2
     , ByteArray -> Int -> Char
indexLatinCharArray (Bytes -> ByteArray
array Bytes
chunk) (Bytes -> Int
offset Bytes
chunk Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
3) Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
c3
     , ByteArray -> Int -> Char
indexLatinCharArray (Bytes -> ByteArray
array Bytes
chunk) (Bytes -> Int
offset Bytes
chunk Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
4) Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
c4
     , ByteArray -> Int -> Char
indexLatinCharArray (Bytes -> ByteArray
array Bytes
chunk) (Bytes -> Int
offset Bytes
chunk Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
5) Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
c5
     , ByteArray -> Int -> Char
indexLatinCharArray (Bytes -> ByteArray
array Bytes
chunk) (Bytes -> Int
offset Bytes
chunk Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
6) Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
c6
     , ByteArray -> Int -> Char
indexLatinCharArray (Bytes -> ByteArray
array Bytes
chunk) (Bytes -> Int
offset Bytes
chunk Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
7) Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
c7
     , ByteArray -> Int -> Char
indexLatinCharArray (Bytes -> ByteArray
array Bytes
chunk) (Bytes -> Int
offset Bytes
chunk Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
8) Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
c8
     , ByteArray -> Int -> Char
indexLatinCharArray (Bytes -> ByteArray
array Bytes
chunk) (Bytes -> Int
offset Bytes
chunk Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
9) Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
c9
         -> () -> Int -> Int -> Result e ()
forall e a. a -> Int -> Int -> Result e a
Success () (Bytes -> Int
offset Bytes
chunk Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
10) (Bytes -> Int
length Bytes
chunk Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
10)
     | Bool
otherwise -> e -> Result e ()
forall e a. e -> Result e a
Failure e
e

-- | Consume eleven characters, failing if they do
-- not match the expected values.
char11 :: e -> Char -> Char -> Char -> Char -> Char -> Char
  -> Char -> Char -> Char -> Char -> Char -> Parser e s ()
{-# inline char11 #-}
char11 :: e
-> Char
-> Char
-> Char
-> Char
-> Char
-> Char
-> Char
-> Char
-> Char
-> Char
-> Char
-> Parser e s ()
char11 e
e !Char
c0 !Char
c1 !Char
c2 !Char
c3 !Char
c4 !Char
c5 !Char
c6 !Char
c7 !Char
c8 !Char
c9 !Char
c10 = (Bytes -> Result e ()) -> Parser e s ()
forall e a s. (Bytes -> Result e a) -> Parser e s a
uneffectful ((Bytes -> Result e ()) -> Parser e s ())
-> (Bytes -> Result e ()) -> Parser e s ()
forall a b. (a -> b) -> a -> b
$ \Bytes
chunk ->
  if | Bytes -> Int
length Bytes
chunk Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
10
     , ByteArray -> Int -> Char
indexLatinCharArray (Bytes -> ByteArray
array Bytes
chunk) (Bytes -> Int
offset Bytes
chunk) Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
c0
     , ByteArray -> Int -> Char
indexLatinCharArray (Bytes -> ByteArray
array Bytes
chunk) (Bytes -> Int
offset Bytes
chunk Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1) Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
c1
     , ByteArray -> Int -> Char
indexLatinCharArray (Bytes -> ByteArray
array Bytes
chunk) (Bytes -> Int
offset Bytes
chunk Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
2) Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
c2
     , ByteArray -> Int -> Char
indexLatinCharArray (Bytes -> ByteArray
array Bytes
chunk) (Bytes -> Int
offset Bytes
chunk Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
3) Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
c3
     , ByteArray -> Int -> Char
indexLatinCharArray (Bytes -> ByteArray
array Bytes
chunk) (Bytes -> Int
offset Bytes
chunk Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
4) Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
c4
     , ByteArray -> Int -> Char
indexLatinCharArray (Bytes -> ByteArray
array Bytes
chunk) (Bytes -> Int
offset Bytes
chunk Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
5) Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
c5
     , ByteArray -> Int -> Char
indexLatinCharArray (Bytes -> ByteArray
array Bytes
chunk) (Bytes -> Int
offset Bytes
chunk Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
6) Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
c6
     , ByteArray -> Int -> Char
indexLatinCharArray (Bytes -> ByteArray
array Bytes
chunk) (Bytes -> Int
offset Bytes
chunk Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
7) Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
c7
     , ByteArray -> Int -> Char
indexLatinCharArray (Bytes -> ByteArray
array Bytes
chunk) (Bytes -> Int
offset Bytes
chunk Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
8) Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
c8
     , ByteArray -> Int -> Char
indexLatinCharArray (Bytes -> ByteArray
array Bytes
chunk) (Bytes -> Int
offset Bytes
chunk Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
9) Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
c9
     , ByteArray -> Int -> Char
indexLatinCharArray (Bytes -> ByteArray
array Bytes
chunk) (Bytes -> Int
offset Bytes
chunk Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
10) Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
c10
         -> () -> Int -> Int -> Result e ()
forall e a. a -> Int -> Int -> Result e a
Success () (Bytes -> Int
offset Bytes
chunk Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
11) (Bytes -> Int
length Bytes
chunk Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
11)
     | Bool
otherwise -> e -> Result e ()
forall e a. e -> Result e a
Failure e
e

-- | Consume twelve characters, failing if they do
-- not match the expected values.
char12 :: e -> Char -> Char -> Char -> Char -> Char -> Char
  -> Char -> Char -> Char -> Char -> Char -> Char -> Parser e s ()
{-# inline char12 #-}
char12 :: e
-> Char
-> Char
-> Char
-> Char
-> Char
-> Char
-> Char
-> Char
-> Char
-> Char
-> Char
-> Char
-> Parser e s ()
char12 e
e !Char
c0 !Char
c1 !Char
c2 !Char
c3 !Char
c4 !Char
c5 !Char
c6 !Char
c7 !Char
c8 !Char
c9 !Char
c10 !Char
c11 = (Bytes -> Result e ()) -> Parser e s ()
forall e a s. (Bytes -> Result e a) -> Parser e s a
uneffectful ((Bytes -> Result e ()) -> Parser e s ())
-> (Bytes -> Result e ()) -> Parser e s ()
forall a b. (a -> b) -> a -> b
$ \Bytes
chunk ->
  if | Bytes -> Int
length Bytes
chunk Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
11
     , ByteArray -> Int -> Char
indexLatinCharArray (Bytes -> ByteArray
array Bytes
chunk) (Bytes -> Int
offset Bytes
chunk) Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
c0
     , ByteArray -> Int -> Char
indexLatinCharArray (Bytes -> ByteArray
array Bytes
chunk) (Bytes -> Int
offset Bytes
chunk Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1) Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
c1
     , ByteArray -> Int -> Char
indexLatinCharArray (Bytes -> ByteArray
array Bytes
chunk) (Bytes -> Int
offset Bytes
chunk Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
2) Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
c2
     , ByteArray -> Int -> Char
indexLatinCharArray (Bytes -> ByteArray
array Bytes
chunk) (Bytes -> Int
offset Bytes
chunk Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
3) Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
c3
     , ByteArray -> Int -> Char
indexLatinCharArray (Bytes -> ByteArray
array Bytes
chunk) (Bytes -> Int
offset Bytes
chunk Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
4) Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
c4
     , ByteArray -> Int -> Char
indexLatinCharArray (Bytes -> ByteArray
array Bytes
chunk) (Bytes -> Int
offset Bytes
chunk Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
5) Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
c5
     , ByteArray -> Int -> Char
indexLatinCharArray (Bytes -> ByteArray
array Bytes
chunk) (Bytes -> Int
offset Bytes
chunk Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
6) Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
c6
     , ByteArray -> Int -> Char
indexLatinCharArray (Bytes -> ByteArray
array Bytes
chunk) (Bytes -> Int
offset Bytes
chunk Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
7) Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
c7
     , ByteArray -> Int -> Char
indexLatinCharArray (Bytes -> ByteArray
array Bytes
chunk) (Bytes -> Int
offset Bytes
chunk Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
8) Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
c8
     , ByteArray -> Int -> Char
indexLatinCharArray (Bytes -> ByteArray
array Bytes
chunk) (Bytes -> Int
offset Bytes
chunk Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
9) Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
c9
     , ByteArray -> Int -> Char
indexLatinCharArray (Bytes -> ByteArray
array Bytes
chunk) (Bytes -> Int
offset Bytes
chunk Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
10) Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
c10
     , ByteArray -> Int -> Char
indexLatinCharArray (Bytes -> ByteArray
array Bytes
chunk) (Bytes -> Int
offset Bytes
chunk Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
11) Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
c11
         -> () -> Int -> Int -> Result e ()
forall e a. a -> Int -> Int -> Result e a
Success () (Bytes -> Int
offset Bytes
chunk Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
12) (Bytes -> Int
length Bytes
chunk Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
12)
     | Bool
otherwise -> e -> Result e ()
forall e a. e -> Result e a
Failure e
e

-- | Consumes and returns the next character in the input.
any :: e -> Parser e s Char
{-# inline any #-}
any :: e -> Parser e s Char
any e
e = (Bytes -> Result e Char) -> Parser e s Char
forall e a s. (Bytes -> Result e a) -> Parser e s a
uneffectful ((Bytes -> Result e Char) -> Parser e s Char)
-> (Bytes -> Result e Char) -> Parser e s Char
forall a b. (a -> b) -> a -> b
$ \Bytes
chunk -> if Bytes -> Int
length Bytes
chunk Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
0
  then
    let c :: Char
c = ByteArray -> Int -> Char
indexLatinCharArray (Bytes -> ByteArray
array Bytes
chunk) (Bytes -> Int
offset Bytes
chunk)
     in Char -> Int -> Int -> Result e Char
forall e a. a -> Int -> Int -> Result e a
Success Char
c (Bytes -> Int
offset Bytes
chunk Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1) (Bytes -> Int
length Bytes
chunk Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1)
  else e -> Result e Char
forall e a. e -> Result e a
Failure e
e

-- | Consume a character from the input or return @Nothing@ if
-- end of the stream has been reached. Since ISO 8859-1 maps every
-- bytes to a character, this parser never fails.
opt :: Parser e s (Maybe Char)
{-# inline opt #-}
opt :: Parser e s (Maybe Char)
opt = (Bytes -> Result e (Maybe Char)) -> Parser e s (Maybe Char)
forall e a s. (Bytes -> Result e a) -> Parser e s a
uneffectful ((Bytes -> Result e (Maybe Char)) -> Parser e s (Maybe Char))
-> (Bytes -> Result e (Maybe Char)) -> Parser e s (Maybe Char)
forall a b. (a -> b) -> a -> b
$ \Bytes
chunk -> case Bytes -> Int
length Bytes
chunk of
  Int
0 -> Maybe Char -> Int -> Int -> Result e (Maybe Char)
forall e a. a -> Int -> Int -> Result e a
Success Maybe Char
forall a. Maybe a
Nothing (Bytes -> Int
offset Bytes
chunk) (Bytes -> Int
length Bytes
chunk)
  Int
_ -> Maybe Char -> Int -> Int -> Result e (Maybe Char)
forall e a. a -> Int -> Int -> Result e a
Success
    (Char -> Maybe Char
forall a. a -> Maybe a
Just (ByteArray -> Int -> Char
indexLatinCharArray (Bytes -> ByteArray
array Bytes
chunk) (Bytes -> Int
offset Bytes
chunk)))
    (Bytes -> Int
offset Bytes
chunk Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1) (Bytes -> Int
length Bytes
chunk Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1)

-- | Variant of @opt@ with unboxed result.
opt# :: Parser e s (# (# #) | Char# #)
{-# inline opt# #-}
opt# :: Parser e s (# (# #) | Char# #)
opt# = ((# ByteArray#, Int#, Int# #)
 -> ST# s (Result# e (# (# #) | Char# #)))
-> Parser e s (# (# #) | Char# #)
forall e s a.
((# ByteArray#, Int#, Int# #) -> ST# s (Result# e a))
-> Parser e s a
Parser
  (\(# ByteArray#
arr, Int#
off, Int#
len #) State# s
s0 -> case Int#
len of
    Int#
0# -> (# State# s
s0, (# | (# (# (# #) | #), Int#
off, Int#
len #) #) #)
    Int#
_ -> (# State# s
s0, (# | (# (# | ByteArray# -> Int# -> Char#
indexCharArray# ByteArray#
arr Int#
off #), Int#
off Int# -> Int# -> Int#
+# Int#
1#, Int#
len Int# -> Int# -> Int#
-# Int#
1# #) #) #)
  )

skipDigitsAsciiLoop ::
     Bytes -- Chunk
  -> (# Int#, Int# #)
skipDigitsAsciiLoop :: Bytes -> (# Int#, Int# #)
skipDigitsAsciiLoop !Bytes
c = if Bytes -> Int
length Bytes
c Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
0
  then
    let w :: Char
w = ByteArray -> Int -> Char
indexLatinCharArray (Bytes -> ByteArray
array Bytes
c) (Bytes -> Int
offset Bytes
c)
     in if Char
w Char -> Char -> Bool
forall a. Ord a => a -> a -> Bool
>= Char
'0' Bool -> Bool -> Bool
&& Char
w Char -> Char -> Bool
forall a. Ord a => a -> a -> Bool
<= Char
'9'
          then Bytes -> (# Int#, Int# #)
skipDigitsAsciiLoop (Int -> Bytes -> Bytes
Bytes.unsafeDrop Int
1 Bytes
c)
          else (# Int -> Int#
unI (Bytes -> Int
offset Bytes
c), Int -> Int#
unI (Bytes -> Int
length Bytes
c) #)
  else (# Int -> Int#
unI (Bytes -> Int
offset Bytes
c), Int -> Int#
unI (Bytes -> Int
length Bytes
c) #)

skipDigitsAscii1LoopStart ::
     e
  -> Bytes -- chunk
  -> Result# e ()
skipDigitsAscii1LoopStart :: e -> Bytes -> Result# e ()
skipDigitsAscii1LoopStart e
e !Bytes
c = if Bytes -> Int
length Bytes
c Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
0
  then
    let w :: Char
w = ByteArray -> Int -> Char
indexLatinCharArray (Bytes -> ByteArray
array Bytes
c) (Bytes -> Int
offset Bytes
c)
     in if Char
w Char -> Char -> Bool
forall a. Ord a => a -> a -> Bool
>= Char
'0' Bool -> Bool -> Bool
&& Char
w Char -> Char -> Bool
forall a. Ord a => a -> a -> Bool
<= Char
'9'
          then (# Int#, Int# #) -> Result# e ()
forall e. (# Int#, Int# #) -> Result# e ()
upcastUnitSuccess (Bytes -> (# Int#, Int# #)
skipDigitsAsciiLoop (Int -> Bytes -> Bytes
Bytes.unsafeDrop Int
1 Bytes
c))
          else (# e
e | #)
  else (# e
e | #)

-- | Variant of 'skipDigits' that requires at least one digit
-- to be present.
skipDigits1 :: e -> Parser e s ()
{-# inline skipDigits1 #-}
skipDigits1 :: e -> Parser e s ()
skipDigits1 e
e = (Bytes -> Result# e ()) -> Parser e s ()
forall e a s. (Bytes -> Result# e a) -> Parser e s a
uneffectful# ((Bytes -> Result# e ()) -> Parser e s ())
-> (Bytes -> Result# e ()) -> Parser e s ()
forall a b. (a -> b) -> a -> b
$ \Bytes
c ->
  e -> Bytes -> Result# e ()
forall e. e -> Bytes -> Result# e ()
skipDigitsAscii1LoopStart e
e Bytes
c

-- | Skip the characters @0-9@ until a non-digit is encountered.
-- This parser does not fail.
skipDigits :: Parser e s ()
skipDigits :: Parser e s ()
skipDigits = (Bytes -> Result# e ()) -> Parser e s ()
forall e a s. (Bytes -> Result# e a) -> Parser e s a
uneffectful# ((Bytes -> Result# e ()) -> Parser e s ())
-> (Bytes -> Result# e ()) -> Parser e s ()
forall a b. (a -> b) -> a -> b
$ \Bytes
c ->
  (# Int#, Int# #) -> Result# e ()
forall e. (# Int#, Int# #) -> Result# e ()
upcastUnitSuccess (Bytes -> (# Int#, Int# #)
skipDigitsAsciiLoop Bytes
c)

unI :: Int -> Int#
{-# inline unI #-}
unI :: Int -> Int#
unI (I# Int#
w) = Int#
w

-- | Skip the character any number of times. This succeeds
-- even if the character was not present.
skipChar :: Char -> Parser e s ()
{-# inline skipChar #-}
skipChar :: Char -> Parser e s ()
skipChar !Char
w = (Bytes -> Result# e ()) -> Parser e s ()
forall e a s. (Bytes -> Result# e a) -> Parser e s a
uneffectful# ((Bytes -> Result# e ()) -> Parser e s ())
-> (Bytes -> Result# e ()) -> Parser e s ()
forall a b. (a -> b) -> a -> b
$ \Bytes
c ->
  (# Int#, Int# #) -> Result# e ()
forall e. (# Int#, Int# #) -> Result# e ()
upcastUnitSuccess (Char -> Bytes -> (# Int#, Int# #)
skipLoop Char
w Bytes
c)

-- | Skip the character any number of times. It must occur
-- at least once or else this will fail.
skipChar1 :: e -> Char -> Parser e s ()
{-# inline skipChar1 #-}
skipChar1 :: e -> Char -> Parser e s ()
skipChar1 e
e !Char
w = (Bytes -> Result# e ()) -> Parser e s ()
forall e a s. (Bytes -> Result# e a) -> Parser e s a
uneffectful# ((Bytes -> Result# e ()) -> Parser e s ())
-> (Bytes -> Result# e ()) -> Parser e s ()
forall a b. (a -> b) -> a -> b
$ \Bytes
c ->
  e -> Char -> Bytes -> Result# e ()
forall e. e -> Char -> Bytes -> Result# e ()
skipLoop1Start e
e Char
w Bytes
c

skipLoop ::
     Char -- byte to match
  -> Bytes -- Chunk
  -> (# Int#, Int# #)
skipLoop :: Char -> Bytes -> (# Int#, Int# #)
skipLoop !Char
w !Bytes
c = if Bytes -> Int
length Bytes
c Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
0
  then if ByteArray -> Int -> Char
indexLatinCharArray (Bytes -> ByteArray
array Bytes
c) (Bytes -> Int
offset Bytes
c) Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
w
    then Char -> Bytes -> (# Int#, Int# #)
skipLoop Char
w (Int -> Bytes -> Bytes
Bytes.unsafeDrop Int
1 Bytes
c)
    else (# Int -> Int#
unI (Bytes -> Int
offset Bytes
c), Int -> Int#
unI (Bytes -> Int
length Bytes
c) #)
  else (# Int -> Int#
unI (Bytes -> Int
offset Bytes
c), Int -> Int#
unI (Bytes -> Int
length Bytes
c) #)

skipLoop1Start ::
     e
  -> Char -- byte to match
  -> Bytes -- chunk
  -> Result# e ()
skipLoop1Start :: e -> Char -> Bytes -> Result# e ()
skipLoop1Start e
e !Char
w !Bytes
chunk0 = if Bytes -> Int
length Bytes
chunk0 Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
0
  then if ByteArray -> Int -> Char
indexLatinCharArray (Bytes -> ByteArray
array Bytes
chunk0) (Bytes -> Int
offset Bytes
chunk0) Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
w
    then (# Int#, Int# #) -> Result# e ()
forall e. (# Int#, Int# #) -> Result# e ()
upcastUnitSuccess (Char -> Bytes -> (# Int#, Int# #)
skipLoop Char
w (Int -> Bytes -> Bytes
Bytes.unsafeDrop Int
1 Bytes
chunk0))
    else (# e
e | #)
  else (# e
e | #)

-- | Parse a decimal-encoded 8-bit word. If the number is larger
-- than 255, this parser fails.
decWord8 :: e -> Parser e s Word8
decWord8 :: e -> Parser e s Word8
decWord8 e
e = ((# ByteArray#, Int#, Int# #) -> ST# s (Result# e Word8))
-> Parser e s Word8
forall e s a.
((# ByteArray#, Int#, Int# #) -> ST# s (Result# e a))
-> Parser e s a
Parser
  (\(# ByteArray#, Int#, Int# #)
chunk0 State# s
s0 -> case e -> Word -> Bytes -> ST# s (Result# e Word#)
forall e s. e -> Word -> Bytes -> ST# s (Result# e Word#)
decSmallWordStart e
e Word
256 ((# ByteArray#, Int#, Int# #) -> Bytes
boxBytes (# ByteArray#, Int#, Int# #)
chunk0) State# s
s0 of
    (# State# s
s1, Result# e Word#
r #) -> (# State# s
s1, Result# e Word# -> Result# e Word8
forall e. Result# e Word# -> Result# e Word8
upcastWord8Result Result# e Word#
r #)
  )

-- | Parse a hexadecimal-encoded 8-bit word. If the number is larger
-- than 255, this parser fails. This allows leading zeroes and is
-- insensitive to case. For example, @00A@, @0a@ and @A@ would all
-- be accepted as the same number.
hexWord8 :: e -> Parser e s Word8
hexWord8 :: e -> Parser e s Word8
hexWord8 e
e = ((# ByteArray#, Int#, Int# #) -> ST# s (Result# e Word8))
-> Parser e s Word8
forall e s a.
((# ByteArray#, Int#, Int# #) -> ST# s (Result# e a))
-> Parser e s a
Parser
  (\(# ByteArray#, Int#, Int# #)
chunk0 State# s
s0 -> case e -> Word -> Bytes -> ST# s (Result# e Word#)
forall e s. e -> Word -> Bytes -> ST# s (Result# e Word#)
hexSmallWordStart e
e Word
256 ((# ByteArray#, Int#, Int# #) -> Bytes
boxBytes (# ByteArray#, Int#, Int# #)
chunk0) State# s
s0 of
    (# State# s
s1, Result# e Word#
r #) -> (# State# s
s1, Result# e Word# -> Result# e Word8
forall e. Result# e Word# -> Result# e Word8
upcastWord8Result Result# e Word#
r #)
  )

-- | Parse a hexadecimal-encoded 16-bit word. If the number is larger
-- than 65535, this parser fails. This allows leading zeroes and is
-- insensitive to case. For example, @0100a@ and @100A@ would both
-- be accepted as the same number.
hexWord16 :: e -> Parser e s Word16
hexWord16 :: e -> Parser e s Word16
hexWord16 e
e = ((# ByteArray#, Int#, Int# #) -> ST# s (Result# e Word16))
-> Parser e s Word16
forall e s a.
((# ByteArray#, Int#, Int# #) -> ST# s (Result# e a))
-> Parser e s a
Parser
  (\(# ByteArray#, Int#, Int# #)
chunk0 State# s
s0 -> case e -> Word -> Bytes -> ST# s (Result# e Word#)
forall e s. e -> Word -> Bytes -> ST# s (Result# e Word#)
hexSmallWordStart e
e Word
65536 ((# ByteArray#, Int#, Int# #) -> Bytes
boxBytes (# ByteArray#, Int#, Int# #)
chunk0) State# s
s0 of
    (# State# s
s1, Result# e Word#
r #) -> (# State# s
s1, Result# e Word# -> Result# e Word16
forall e. Result# e Word# -> Result# e Word16
upcastWord16Result Result# e Word#
r #)
  )

-- | Parse a decimal-encoded 16-bit word. If the number is larger
-- than 65535, this parser fails.
decWord16 :: e -> Parser e s Word16
decWord16 :: e -> Parser e s Word16
decWord16 e
e = ((# ByteArray#, Int#, Int# #) -> ST# s (Result# e Word16))
-> Parser e s Word16
forall e s a.
((# ByteArray#, Int#, Int# #) -> ST# s (Result# e a))
-> Parser e s a
Parser
  (\(# ByteArray#, Int#, Int# #)
chunk0 State# s
s0 -> case e -> Word -> Bytes -> ST# s (Result# e Word#)
forall e s. e -> Word -> Bytes -> ST# s (Result# e Word#)
decSmallWordStart e
e Word
65536 ((# ByteArray#, Int#, Int# #) -> Bytes
boxBytes (# ByteArray#, Int#, Int# #)
chunk0) State# s
s0 of
    (# State# s
s1, Result# e Word#
r #) -> (# State# s
s1, Result# e Word# -> Result# e Word16
forall e. Result# e Word# -> Result# e Word16
upcastWord16Result Result# e Word#
r #)
  )

-- | Parse a decimal-encoded 32-bit word. If the number is larger
-- than 4294967295, this parser fails.
decWord32 :: e -> Parser e s Word32
-- This will not work on 32-bit platforms.
decWord32 :: e -> Parser e s Word32
decWord32 e
e = ((# ByteArray#, Int#, Int# #) -> ST# s (Result# e Word32))
-> Parser e s Word32
forall e s a.
((# ByteArray#, Int#, Int# #) -> ST# s (Result# e a))
-> Parser e s a
Parser
  (\(# ByteArray#, Int#, Int# #)
chunk0 State# s
s0 -> case e -> Word -> Bytes -> ST# s (Result# e Word#)
forall e s. e -> Word -> Bytes -> ST# s (Result# e Word#)
decSmallWordStart e
e Word
4294967296 ((# ByteArray#, Int#, Int# #) -> Bytes
boxBytes (# ByteArray#, Int#, Int# #)
chunk0) State# s
s0 of
    (# State# s
s1, Result# e Word#
r #) -> (# State# s
s1, Result# e Word# -> Result# e Word32
forall e. Result# e Word# -> Result# e Word32
upcastWord32Result Result# e Word#
r #)
  )

-- | Parse a decimal-encoded number. If the number is too large to be
-- represented by a machine word, this fails with the provided
-- error message. This accepts any number of leading zeroes.
decWord :: e -> Parser e s Word
decWord :: e -> Parser e s Word
decWord e
e = ((# ByteArray#, Int#, Int# #) -> ST# s (Result# e Word))
-> Parser e s Word
forall e s a.
((# ByteArray#, Int#, Int# #) -> ST# s (Result# e a))
-> Parser e s a
Parser
  (\(# ByteArray#, Int#, Int# #)
chunk0 State# s
s0 -> case e -> Bytes -> ST# s (Result# e Word#)
forall e s. e -> Bytes -> ST# s (Result# e Word#)
decWordStart e
e ((# ByteArray#, Int#, Int# #) -> Bytes
boxBytes (# ByteArray#, Int#, Int# #)
chunk0) State# s
s0 of
    (# State# s
s1, Result# e Word#
r #) -> (# State# s
s1, Result# e Word# -> Result# e Word
forall e. Result# e Word# -> Result# e Word
upcastWordResult Result# e Word#
r #)
  )

-- | Parse a decimal-encoded unsigned number. If the number is
-- too large to be represented by a 64-bit word, this fails with
-- the provided error message. This accepts any number of leading
-- zeroes.
decWord64 :: e -> Parser e s Word64
decWord64 :: e -> Parser e s Word64
decWord64 e
e = ((# ByteArray#, Int#, Int# #) -> ST# s (Result# e Word64))
-> Parser e s Word64
forall e s a.
((# ByteArray#, Int#, Int# #) -> ST# s (Result# e a))
-> Parser e s a
Parser
  (\(# ByteArray#, Int#, Int# #)
chunk0 State# s
s0 -> case e -> Bytes -> ST# s (Result# e Word#)
forall e s. e -> Bytes -> ST# s (Result# e Word#)
decWordStart e
e ((# ByteArray#, Int#, Int# #) -> Bytes
boxBytes (# ByteArray#, Int#, Int# #)
chunk0) State# s
s0 of
    (# State# s
s1, Result# e Word#
r #) -> (# State# s
s1, Result# e Word# -> Result# e Word64
forall e. Result# e Word# -> Result# e Word64
upcastWord64Result Result# e Word#
r #)
  )

hexSmallWordStart ::
     e -- Error message
  -> Word -- Upper Bound
  -> Bytes -- Chunk
  -> ST# s (Result# e Word# )
hexSmallWordStart :: e -> Word -> Bytes -> ST# s (Result# e Word#)
hexSmallWordStart e
e !Word
limit !Bytes
chunk0 State# s
s0 = if Bytes -> Int
length Bytes
chunk0 Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
0
  then case Word8 -> Maybe Word
oneHexMaybe (ByteArray -> Int -> Word8
forall a. Prim a => ByteArray -> Int -> a
PM.indexByteArray (Bytes -> ByteArray
array Bytes
chunk0) (Bytes -> Int
offset Bytes
chunk0)) of
    Maybe Word
Nothing -> (# State# s
s0, (# e
e | #) #)
    Just Word
w -> (# State# s
s0, e -> Word -> Word -> Bytes -> Result# e Word#
forall e. e -> Word -> Word -> Bytes -> Result# e Word#
hexSmallWordMore e
e Word
w Word
limit (Int -> Bytes -> Bytes
Bytes.unsafeDrop Int
1 Bytes
chunk0) #)
  else (# State# s
s0, (# e
e | #) #)

decSmallWordStart ::
     e -- Error message
  -> Word -- Upper Bound
  -> Bytes -- Chunk
  -> ST# s (Result# e Word# )
decSmallWordStart :: e -> Word -> Bytes -> ST# s (Result# e Word#)
decSmallWordStart e
e !Word
limit !Bytes
chunk0 State# s
s0 = if Bytes -> Int
length Bytes
chunk0 Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
0
  then
    let !w :: Word
w = Word8 -> Word
forall a b. (Integral a, Num b) => a -> b
fromIntegral @Word8 @Word
          (ByteArray -> Int -> Word8
forall a. Prim a => ByteArray -> Int -> a
PM.indexByteArray (Bytes -> ByteArray
array Bytes
chunk0) (Bytes -> Int
offset Bytes
chunk0)) Word -> Word -> Word
forall a. Num a => a -> a -> a
- Word
48
     in if Word
w Word -> Word -> Bool
forall a. Ord a => a -> a -> Bool
< Word
10
          then (# State# s
s0, e -> Word -> Word -> Bytes -> Result# e Word#
forall e. e -> Word -> Word -> Bytes -> Result# e Word#
decSmallWordMore e
e Word
w Word
limit (Int -> Bytes -> Bytes
Bytes.unsafeDrop Int
1 Bytes
chunk0) #)
          else (# State# s
s0, (# e
e | #) #)
  else (# State# s
s0, (# e
e | #) #)

-- This will not inline since it is recursive, but worker
-- wrapper will still happen.
decWordMore ::
     e -- Error message
  -> Word -- Accumulator
  -> Bytes -- Chunk
  -> Result# e Word#
decWordMore :: e -> Word -> Bytes -> Result# e Word#
decWordMore e
e !Word
acc !Bytes
chunk0 = case Int
len of
  Int
0 -> (# | (# Word -> Word#
unW (Word -> Word
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word
acc), Int -> Int#
unI (Bytes -> Int
offset Bytes
chunk0), Int#
0# #) #)
  Int
_ ->
    let !w :: Word
w = Word8 -> Word
forall a b. (Integral a, Num b) => a -> b
fromIntegral @Word8 @Word
          (ByteArray -> Int -> Word8
forall a. Prim a => ByteArray -> Int -> a
PM.indexByteArray (Bytes -> ByteArray
array Bytes
chunk0) (Bytes -> Int
offset Bytes
chunk0)) Word -> Word -> Word
forall a. Num a => a -> a -> a
- Word
48
     in if Word
w Word -> Word -> Bool
forall a. Ord a => a -> a -> Bool
< Word
10
          then
            let (Bool
overflow,Word
acc') = Word -> Word -> (Bool, Word)
unsignedPushBase10 Word
acc Word
w
             in if Bool
overflow
               then (# e
e | #)
               else e -> Word -> Bytes -> Result# e Word#
forall e. e -> Word -> Bytes -> Result# e Word#
decWordMore e
e Word
acc' (Int -> Bytes -> Bytes
Bytes.unsafeDrop Int
1 Bytes
chunk0)
          else (# | (# Word -> Word#
unW (Word -> Word
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word
acc), Int -> Int#
unI (Bytes -> Int
offset Bytes
chunk0), Int#
len# #) #)
  where
  !len :: Int
len@(I# Int#
len# ) = Bytes -> Int
length Bytes
chunk0

upcastWordResult :: Result# e Word# -> Result# e Word
{-# inline upcastWordResult #-}
upcastWordResult :: Result# e Word# -> Result# e Word
upcastWordResult (# e
e | #) = (# e
e | #)
upcastWordResult (# | (# Word#
a, Int#
b, Int#
c #) #) = (# | (# Word# -> Word
W# Word#
a, Int#
b, Int#
c #) #)

-- This only works on 64-bit platforms.
upcastWord64Result :: Result# e Word# -> Result# e Word64
{-# inline upcastWord64Result #-}
upcastWord64Result :: Result# e Word# -> Result# e Word64
upcastWord64Result (# e
e | #) = (# e
e | #)
upcastWord64Result (# | (# Word#
a, Int#
b, Int#
c #) #) = (# | (# Word# -> Word64
W64# Word#
a, Int#
b, Int#
c #) #)

hexSmallWordMore ::
     e -- Error message
  -> Word -- Accumulator
  -> Word -- Upper Bound
  -> Bytes -- Chunk
  -> Result# e Word#
hexSmallWordMore :: e -> Word -> Word -> Bytes -> Result# e Word#
hexSmallWordMore e
e !Word
acc !Word
limit !Bytes
chunk0 = if Bytes -> Int
length Bytes
chunk0 Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
0
  then case Word8 -> Maybe Word
oneHexMaybe (ByteArray -> Int -> Word8
forall a. Prim a => ByteArray -> Int -> a
PM.indexByteArray (Bytes -> ByteArray
array Bytes
chunk0) (Bytes -> Int
offset Bytes
chunk0)) of
    Maybe Word
Nothing -> (# | (# Word -> Word#
unW Word
acc, Int -> Int#
unI (Bytes -> Int
offset Bytes
chunk0), Int -> Int#
unI (Bytes -> Int
length Bytes
chunk0)  #) #)
    Just Word
w -> let w' :: Word
w' = Word
acc Word -> Word -> Word
forall a. Num a => a -> a -> a
* Word
16 Word -> Word -> Word
forall a. Num a => a -> a -> a
+ Word
w in
      if Word
w' Word -> Word -> Bool
forall a. Ord a => a -> a -> Bool
< Word
limit
        then e -> Word -> Word -> Bytes -> Result# e Word#
forall e. e -> Word -> Word -> Bytes -> Result# e Word#
hexSmallWordMore e
e Word
w' Word
limit (Int -> Bytes -> Bytes
Bytes.unsafeDrop Int
1 Bytes
chunk0)
        else (# e
e | #)
  else (# | (# Word -> Word#
unW Word
acc, Int -> Int#
unI (Bytes -> Int
offset Bytes
chunk0), Int#
0# #) #)

decSmallWordMore ::
     e -- Error message
  -> Word -- Accumulator
  -> Word -- Upper Bound
  -> Bytes -- Chunk
  -> Result# e Word#
decSmallWordMore :: e -> Word -> Word -> Bytes -> Result# e Word#
decSmallWordMore e
e !Word
acc !Word
limit !Bytes
chunk0 = if Bytes -> Int
length Bytes
chunk0 Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
0
  then
    let !w :: Word
w = Word8 -> Word
forall a b. (Integral a, Num b) => a -> b
fromIntegral @Word8 @Word
          (ByteArray -> Int -> Word8
forall a. Prim a => ByteArray -> Int -> a
PM.indexByteArray (Bytes -> ByteArray
array Bytes
chunk0) (Bytes -> Int
offset Bytes
chunk0)) Word -> Word -> Word
forall a. Num a => a -> a -> a
- Word
48
     in if Word
w Word -> Word -> Bool
forall a. Ord a => a -> a -> Bool
< Word
10
          then
            let w' :: Word
w' = Word
acc Word -> Word -> Word
forall a. Num a => a -> a -> a
* Word
10 Word -> Word -> Word
forall a. Num a => a -> a -> a
+ Word
w
             in if Word
w' Word -> Word -> Bool
forall a. Ord a => a -> a -> Bool
< Word
limit
                  then e -> Word -> Word -> Bytes -> Result# e Word#
forall e. e -> Word -> Word -> Bytes -> Result# e Word#
decSmallWordMore e
e Word
w' Word
limit (Int -> Bytes -> Bytes
Bytes.unsafeDrop Int
1 Bytes
chunk0)
                  else (# e
e | #)
          else (# | (# Word -> Word#
unW Word
acc, Int -> Int#
unI (Bytes -> Int
offset Bytes
chunk0), Int -> Int#
unI (Bytes -> Int
length Bytes
chunk0)  #) #)
  else (# | (# Word -> Word#
unW Word
acc, Int -> Int#
unI (Bytes -> Int
offset Bytes
chunk0), Int#
0# #) #)

unW :: Word -> Word#
{-# inline unW #-}
unW :: Word -> Word#
unW (W# Word#
w) = Word#
w

decWordStart ::
     e -- Error message
  -> Bytes -- Chunk
  -> ST# s (Result# e Word# )
decWordStart :: e -> Bytes -> ST# s (Result# e Word#)
decWordStart e
e !Bytes
chunk0 State# s
s0 = if Bytes -> Int
length Bytes
chunk0 Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
0
  then
    let !w :: Word
w = Word8 -> Word
forall a b. (Integral a, Num b) => a -> b
fromIntegral @Word8 @Word
          (ByteArray -> Int -> Word8
forall a. Prim a => ByteArray -> Int -> a
PM.indexByteArray (Bytes -> ByteArray
array Bytes
chunk0) (Bytes -> Int
offset Bytes
chunk0)) Word -> Word -> Word
forall a. Num a => a -> a -> a
- Word
48
     in if Word
w Word -> Word -> Bool
forall a. Ord a => a -> a -> Bool
< Word
10
          then (# State# s
s0, e -> Word -> Bytes -> Result# e Word#
forall e. e -> Word -> Bytes -> Result# e Word#
decWordMore e
e Word
w (Int -> Bytes -> Bytes
Bytes.unsafeDrop Int
1 Bytes
chunk0) #)
          else (# State# s
s0, (# e
e | #) #)
  else (# State# s
s0, (# e
e | #) #)

-- Precondition: the word is small enough
upcastWord16Result :: Result# e Word# -> Result# e Word16
{-# inline upcastWord16Result #-}
upcastWord16Result :: Result# e Word# -> Result# e Word16
upcastWord16Result (# e
e | #) = (# e
e | #)
upcastWord16Result (# | (# Word#
a, Int#
b, Int#
c #) #) = (# | (# Word# -> Word16
W16# (
#if MIN_VERSION_base(4,16,0)
  Exts.wordToWord16#
#endif
  Word#
a), Int#
b, Int#
c #) #)

-- Precondition: the word is small enough
upcastWord32Result :: Result# e Word# -> Result# e Word32
{-# inline upcastWord32Result #-}
upcastWord32Result :: Result# e Word# -> Result# e Word32
upcastWord32Result (# e
e | #) = (# e
e | #)
upcastWord32Result (# | (# Word#
a, Int#
b, Int#
c #) #) = (# | (# Word# -> Word32
W32# (
#if MIN_VERSION_base(4,16,0)
  Exts.wordToWord32#
#endif
  Word#
a), Int#
b, Int#
c #) #)

-- Precondition: the word is small enough
upcastWord8Result :: Result# e Word# -> Result# e Word8
{-# inline upcastWord8Result #-}
upcastWord8Result :: Result# e Word# -> Result# e Word8
upcastWord8Result (# e
e | #) = (# e
e | #)
upcastWord8Result (# | (# Word#
a, Int#
b, Int#
c #) #) = (# | (# Word# -> Word8
W8# (
#if MIN_VERSION_base(4,16,0)
  Exts.wordToWord8#
#endif
  Word#
a), Int#
b, Int#
c #) #)

-- | Parse a decimal-encoded number. If the number is too large to be
-- represented by a machine integer, this fails with the provided
-- error message. This rejects input with that is preceeded by plus
-- or minus. Consequently, it does not parse negative numbers. Use
-- 'decStandardInt' or 'decSignedInt' for that purpose. On a 64-bit
-- platform 'decWord' will successfully parse 9223372036854775808
-- (i.e. @2 ^ 63@), but 'decUnsignedInt' will fail. This parser allows
-- leading zeroes.
decUnsignedInt :: e -> Parser e s Int
decUnsignedInt :: e -> Parser e s Int
decUnsignedInt e
e = ((# ByteArray#, Int#, Int# #) -> ST# s (Result# e Int))
-> Parser e s Int
forall e s a.
((# ByteArray#, Int#, Int# #) -> ST# s (Result# e a))
-> Parser e s a
Parser
  (\(# ByteArray#, Int#, Int# #)
chunk0 State# s
s0 -> case e -> Bytes -> ST# s (Result# e Int#)
forall e s. e -> Bytes -> ST# s (Result# e Int#)
decPosIntStart e
e ((# ByteArray#, Int#, Int# #) -> Bytes
boxBytes (# ByteArray#, Int#, Int# #)
chunk0) State# s
s0 of
    (# State# s
s1, Result# e Int#
r #) -> (# State# s
s1, Result# e Int# -> Result# e Int
forall e. Result# e Int# -> Result# e Int
upcastIntResult Result# e Int#
r #)
  )

-- | Variant of 'decUnsignedInt' with an unboxed result.
decUnsignedInt# :: e -> Parser e s Int#
decUnsignedInt# :: e -> Parser e s Int#
decUnsignedInt# e
e = ((# ByteArray#, Int#, Int# #) -> ST# s (Result# e Int#))
-> Parser e s Int#
forall e s a.
((# ByteArray#, Int#, Int# #) -> ST# s (Result# e a))
-> Parser e s a
Parser
  (\(# ByteArray#, Int#, Int# #)
chunk0 State# s
s0 -> e -> Bytes -> ST# s (Result# e Int#)
forall e s. e -> Bytes -> ST# s (Result# e Int#)
decPosIntStart e
e ((# ByteArray#, Int#, Int# #) -> Bytes
boxBytes (# ByteArray#, Int#, Int# #)
chunk0) State# s
s0)

-- | Parse a decimal-encoded number. If the number is too large to be
-- represented by a machine integer, this fails with the provided
-- error message. This allows the number to optionally be prefixed
-- by plus or minus. If the sign prefix is not present, the number
-- is interpreted as positive. This allows leading zeroes.
decSignedInt :: e -> Parser e s Int
decSignedInt :: e -> Parser e s Int
decSignedInt e
e = ((# ByteArray#, Int#, Int# #) -> ST# s (Result# e Int))
-> Parser e s Int
forall e s a.
((# ByteArray#, Int#, Int# #) -> ST# s (Result# e a))
-> Parser e s a
Parser
  (\(# ByteArray#, Int#, Int# #)
chunk0 State# s
s0 -> case Parser e s Int#
-> (# ByteArray#, Int#, Int# #) -> ST# s (Result# e Int#)
forall e s a.
Parser e s a -> (# ByteArray#, Int#, Int# #) -> ST# s (Result# e a)
runParser (e -> Parser e s Int#
forall e s. e -> Parser e s Int#
decSignedInt# e
e) (# ByteArray#, Int#, Int# #)
chunk0 State# s
s0 of
    (# State# s
s1, Result# e Int#
r #) -> (# State# s
s1, Result# e Int# -> Result# e Int
forall e. Result# e Int# -> Result# e Int
upcastIntResult Result# e Int#
r #)
  )

-- | Variant of 'decUnsignedInt' that lets the caller supply a leading
-- digit. This is useful when parsing formats like JSON where integers with
-- leading zeroes are considered invalid. The calling context must
-- consume the first digit before calling this parser. Results are
-- always positive numbers.
decTrailingInt ::
     e -- ^ Error message
  -> Int -- ^ Leading digit, should be between @0@ and @9@.
  -> Parser e s Int
decTrailingInt :: e -> Int -> Parser e s Int
decTrailingInt e
e (I# Int#
w) = ((# ByteArray#, Int#, Int# #) -> ST# s (Result# e Int))
-> Parser e s Int
forall e s a.
((# ByteArray#, Int#, Int# #) -> ST# s (Result# e a))
-> Parser e s a
Parser
  (\(# ByteArray#, Int#, Int# #)
chunk0 State# s
s0 -> case Parser e s Int#
-> (# ByteArray#, Int#, Int# #) -> ST# s (Result# e Int#)
forall e s a.
Parser e s a -> (# ByteArray#, Int#, Int# #) -> ST# s (Result# e a)
runParser (e -> Int# -> Parser e s Int#
forall e s. e -> Int# -> Parser e s Int#
decTrailingInt# e
e Int#
w) (# ByteArray#, Int#, Int# #)
chunk0 State# s
s0 of
    (# State# s
s1, Result# e Int#
r #) -> (# State# s
s1, Result# e Int# -> Result# e Int
forall e. Result# e Int# -> Result# e Int
upcastIntResult Result# e Int#
r #)
  )

decTrailingInt# ::
     e -- Error message
  -> Int# -- Leading digit, should be between @0@ and @9@.
  -> Parser e s Int#
decTrailingInt# :: e -> Int# -> Parser e s Int#
decTrailingInt# e
e !Int#
w =
  ((# ByteArray#, Int#, Int# #) -> ST# s (Result# e Int#))
-> Parser e s Int#
forall e s a.
((# ByteArray#, Int#, Int# #) -> ST# s (Result# e a))
-> Parser e s a
Parser (\(# ByteArray#, Int#, Int# #)
chunk0 State# s
s0 -> (# State# s
s0, e -> Word -> Word -> Bytes -> Result# e Int#
forall e. e -> Word -> Word -> Bytes -> Result# e Int#
decPosIntMore e
e (Word# -> Word
W# (Int# -> Word#
int2Word# Int#
w)) Word
maxIntAsWord ((# ByteArray#, Int#, Int# #) -> Bytes
boxBytes (# ByteArray#, Int#, Int# #)
chunk0) #))

maxIntAsWord :: Word
maxIntAsWord :: Word
maxIntAsWord = Int -> Word
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int
forall a. Bounded a => a
maxBound :: Int)

-- | Parse a decimal-encoded number. If the number is too large to be
-- represented by a machine integer, this fails with the provided
-- error message. This allows the number to optionally be prefixed
-- by minus. If the minus prefix is not present, the number
-- is interpreted as positive. The disallows a leading plus sign.
-- For example, 'decStandardInt' rejects @+42@, but 'decSignedInt'
-- allows it.
decStandardInt :: e -> Parser e s Int
decStandardInt :: e -> Parser e s Int
decStandardInt e
e = ((# ByteArray#, Int#, Int# #) -> ST# s (Result# e Int))
-> Parser e s Int
forall e s a.
((# ByteArray#, Int#, Int# #) -> ST# s (Result# e a))
-> Parser e s a
Parser
  (\(# ByteArray#, Int#, Int# #)
chunk0 State# s
s0 -> case Parser e s Int#
-> (# ByteArray#, Int#, Int# #) -> ST# s (Result# e Int#)
forall e s a.
Parser e s a -> (# ByteArray#, Int#, Int# #) -> ST# s (Result# e a)
runParser (e -> Parser e s Int#
forall e s. e -> Parser e s Int#
decStandardInt# e
e) (# ByteArray#, Int#, Int# #)
chunk0 State# s
s0 of
    (# State# s
s1, Result# e Int#
r #) -> (# State# s
s1, Result# e Int# -> Result# e Int
forall e. Result# e Int# -> Result# e Int
upcastIntResult Result# e Int#
r #)
  )

decSignedInt# :: e -> Parser e s Int#
{-# noinline decSignedInt# #-}
decSignedInt# :: e -> Parser e s Int#
decSignedInt# e
e = e -> Parser e s Char
forall e s. e -> Parser e s Char
any e
e Parser e s Char -> (Char -> Parser e s Int#) -> Parser e s Int#
forall s e a.
Parser s e a -> (a -> Parser s e Int#) -> Parser s e Int#
`bindFromLiftedToInt` \Char
c -> case Char
c of
  Char
'+' -> ((# ByteArray#, Int#, Int# #) -> ST# s (Result# e Int#))
-> Parser e s Int#
forall e s a.
((# ByteArray#, Int#, Int# #) -> ST# s (Result# e a))
-> Parser e s a
Parser -- plus sign
    (\(# ByteArray#, Int#, Int# #)
chunk0 State# s
s0 -> e -> Bytes -> ST# s (Result# e Int#)
forall e s. e -> Bytes -> ST# s (Result# e Int#)
decPosIntStart e
e ((# ByteArray#, Int#, Int# #) -> Bytes
boxBytes (# ByteArray#, Int#, Int# #)
chunk0) State# s
s0)
  Char
'-' -> ((# ByteArray#, Int#, Int# #) -> ST# s (Result# e Int#))
-> Parser e s Int#
forall e s a.
((# ByteArray#, Int#, Int# #) -> ST# s (Result# e a))
-> Parser e s a
Parser -- minus sign
    (\(# ByteArray#, Int#, Int# #)
chunk0 State# s
s0 -> e -> Bytes -> ST# s (Result# e Int#)
forall e s. e -> Bytes -> ST# s (Result# e Int#)
decNegIntStart e
e ((# ByteArray#, Int#, Int# #) -> Bytes
boxBytes (# ByteArray#, Int#, Int# #)
chunk0) State# s
s0)
  Char
_ -> ((# ByteArray#, Int#, Int# #) -> ST# s (Result# e Int#))
-> Parser e s Int#
forall e s a.
((# ByteArray#, Int#, Int# #) -> ST# s (Result# e a))
-> Parser e s a
Parser -- no sign, there should be a digit here
    (\(# ByteArray#, Int#, Int# #)
chunk0 State# s
s0 ->
      let !w :: Word
w = Char -> Word
char2Word Char
c Word -> Word -> Word
forall a. Num a => a -> a -> a
- Word
48
        in if Word
w Word -> Word -> Bool
forall a. Ord a => a -> a -> Bool
< Word
10
             then (# State# s
s0, e -> Word -> Word -> Bytes -> Result# e Int#
forall e. e -> Word -> Word -> Bytes -> Result# e Int#
decPosIntMore e
e Word
w Word
maxIntAsWord ((# ByteArray#, Int#, Int# #) -> Bytes
boxBytes (# ByteArray#, Int#, Int# #)
chunk0) #)
             else (# State# s
s0, (# e
e | #) #)
    )

-- This is the same as decSignedInt except that we disallow
-- a leading plus sign.
decStandardInt# :: e -> Parser e s Int#
{-# noinline decStandardInt# #-}
decStandardInt# :: e -> Parser e s Int#
decStandardInt# e
e = e -> Parser e s Char
forall e s. e -> Parser e s Char
any e
e Parser e s Char -> (Char -> Parser e s Int#) -> Parser e s Int#
forall s e a.
Parser s e a -> (a -> Parser s e Int#) -> Parser s e Int#
`bindFromLiftedToInt` \Char
c -> case Char
c of
  Char
'-' -> ((# ByteArray#, Int#, Int# #) -> ST# s (Result# e Int#))
-> Parser e s Int#
forall e s a.
((# ByteArray#, Int#, Int# #) -> ST# s (Result# e a))
-> Parser e s a
Parser -- minus sign
    (\(# ByteArray#, Int#, Int# #)
chunk0 State# s
s0 -> e -> Bytes -> ST# s (Result# e Int#)
forall e s. e -> Bytes -> ST# s (Result# e Int#)
decNegIntStart e
e ((# ByteArray#, Int#, Int# #) -> Bytes
boxBytes (# ByteArray#, Int#, Int# #)
chunk0) State# s
s0)
  Char
_ -> ((# ByteArray#, Int#, Int# #) -> ST# s (Result# e Int#))
-> Parser e s Int#
forall e s a.
((# ByteArray#, Int#, Int# #) -> ST# s (Result# e a))
-> Parser e s a
Parser -- no sign, there should be a digit here
    (\(# ByteArray#, Int#, Int# #)
chunk0 State# s
s0 ->
      let !w :: Word
w = Char -> Word
char2Word Char
c Word -> Word -> Word
forall a. Num a => a -> a -> a
- Word
48
        in if Word
w Word -> Word -> Bool
forall a. Ord a => a -> a -> Bool
< Word
10
             then (# State# s
s0, e -> Word -> Word -> Bytes -> Result# e Int#
forall e. e -> Word -> Word -> Bytes -> Result# e Int#
decPosIntMore e
e Word
w Word
maxIntAsWord ((# ByteArray#, Int#, Int# #) -> Bytes
boxBytes (# ByteArray#, Int#, Int# #)
chunk0) #)
             else (# State# s
s0, (# e
e | #) #)
    )

-- | Variant of 'decUnsignedInteger' that lets the caller supply a leading
-- digit. This is useful when parsing formats like JSON where integers with
-- leading zeroes are considered invalid. The calling context must
-- consume the first digit before calling this parser. Results are
-- always positive numbers.
decTrailingInteger ::
     Int -- ^ Leading digit, should be between @0@ and @9@.
  -> Parser e s Integer
decTrailingInteger :: Int -> Parser e s Integer
decTrailingInteger (I# Int#
w) =
  ((# ByteArray#, Int#, Int# #) -> ST# s (Result# e Integer))
-> Parser e s Integer
forall e s a.
((# ByteArray#, Int#, Int# #) -> ST# s (Result# e a))
-> Parser e s a
Parser (\(# ByteArray#, Int#, Int# #)
chunk0 State# s
s0 -> (# State# s
s0, (# | Int -> Int -> Integer -> Bytes -> (# Integer, Int#, Int# #)
decIntegerChunks (Int# -> Int
I# Int#
w) Int
10 Integer
0 ((# ByteArray#, Int#, Int# #) -> Bytes
boxBytes (# ByteArray#, Int#, Int# #)
chunk0) #) #))

-- | Parse a decimal-encoded positive integer of arbitrary
-- size. This rejects input that begins with a plus or minus
-- sign.
decUnsignedInteger :: e -> Parser e s Integer
decUnsignedInteger :: e -> Parser e s Integer
decUnsignedInteger e
e = ((# ByteArray#, Int#, Int# #) -> ST# s (Result# e Integer))
-> Parser e s Integer
forall e s a.
((# ByteArray#, Int#, Int# #) -> ST# s (Result# e a))
-> Parser e s a
Parser
  (\(# ByteArray#, Int#, Int# #)
chunk0 State# s
s0 -> e -> Bytes -> ST# s (Result# e Integer)
forall e s. e -> Bytes -> ST# s (Result# e Integer)
decUnsignedIntegerStart e
e ((# ByteArray#, Int#, Int# #) -> Bytes
boxBytes (# ByteArray#, Int#, Int# #)
chunk0) State# s
s0)

-- | Parse a decimal-encoded integer of arbitrary size.
-- This accepts input that begins with a plus or minus sign.
-- Input without a sign prefix is interpreted as positive.
decSignedInteger :: e -> Parser e s Integer
{-# noinline decSignedInteger #-}
decSignedInteger :: e -> Parser e s Integer
decSignedInteger e
e = e -> Parser e s Char
forall e s. e -> Parser e s Char
any e
e Parser e s Char
-> (Char -> Parser e s Integer) -> Parser e s Integer
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \Char
c -> case Char
c of
  Char
'+' -> do
    e -> Parser e s Integer
forall e s. e -> Parser e s Integer
decUnsignedInteger e
e
  Char
'-' -> do
    Integer
x <- e -> Parser e s Integer
forall e s. e -> Parser e s Integer
decUnsignedInteger e
e
    Integer -> Parser e s Integer
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Integer -> Parser e s Integer) -> Integer -> Parser e s Integer
forall a b. (a -> b) -> a -> b
$! Integer -> Integer
forall a. Num a => a -> a
negate Integer
x
  Char
_ -> ((# ByteArray#, Int#, Int# #) -> ST# s (Result# e Integer))
-> Parser e s Integer
forall e s a.
((# ByteArray#, Int#, Int# #) -> ST# s (Result# e a))
-> Parser e s a
Parser -- no sign, there should be a digit here
    (\(# ByteArray#, Int#, Int# #)
chunk0 State# s
s0 ->
      let !w :: Word
w = Char -> Word
char2Word Char
c Word -> Word -> Word
forall a. Num a => a -> a -> a
- Word
48 in
      if Word
w Word -> Word -> Bool
forall a. Ord a => a -> a -> Bool
< Word
10
        then
          let !r :: (# Integer, Int#, Int# #)
r = Int -> Int -> Integer -> Bytes -> (# Integer, Int#, Int# #)
decIntegerChunks
                (Word -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral @Word @Int Word
w)
                Int
10
                Integer
0
                ((# ByteArray#, Int#, Int# #) -> Bytes
boxBytes (# ByteArray#, Int#, Int# #)
chunk0)
           in (# State# s
s0, (# | (# Integer, Int#, Int# #)
r #) #)
        else (# State# s
s0, (# e
e | #) #)
    )

decPosIntStart ::
     e -- Error message
  -> Bytes -- Chunk
  -> ST# s (Result# e Int# )
decPosIntStart :: e -> Bytes -> ST# s (Result# e Int#)
decPosIntStart e
e !Bytes
chunk0 State# s
s0 = if Bytes -> Int
length Bytes
chunk0 Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
0
  then
    let !w :: Word
w = Word8 -> Word
forall a b. (Integral a, Num b) => a -> b
fromIntegral @Word8 @Word
          (ByteArray -> Int -> Word8
forall a. Prim a => ByteArray -> Int -> a
PM.indexByteArray (Bytes -> ByteArray
array Bytes
chunk0) (Bytes -> Int
offset Bytes
chunk0)) Word -> Word -> Word
forall a. Num a => a -> a -> a
- Word
48
     in if Word
w Word -> Word -> Bool
forall a. Ord a => a -> a -> Bool
< Word
10
          then (# State# s
s0, e -> Word -> Word -> Bytes -> Result# e Int#
forall e. e -> Word -> Word -> Bytes -> Result# e Int#
decPosIntMore e
e Word
w Word
maxIntAsWord (Int -> Bytes -> Bytes
Bytes.unsafeDrop Int
1 Bytes
chunk0) #)
          else (# State# s
s0, (# e
e | #) #)
  else (# State# s
s0, (# e
e | #) #)

decNegIntStart ::
     e -- Error message
  -> Bytes -- Chunk
  -> ST# s (Result# e Int# )
decNegIntStart :: e -> Bytes -> ST# s (Result# e Int#)
decNegIntStart e
e !Bytes
chunk0 State# s
s0 = if Bytes -> Int
length Bytes
chunk0 Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
0
  then
    let !w :: Word
w = Word8 -> Word
forall a b. (Integral a, Num b) => a -> b
fromIntegral @Word8 @Word
          (ByteArray -> Int -> Word8
forall a. Prim a => ByteArray -> Int -> a
PM.indexByteArray (Bytes -> ByteArray
array Bytes
chunk0) (Bytes -> Int
offset Bytes
chunk0)) Word -> Word -> Word
forall a. Num a => a -> a -> a
- Word
48
     in if Word
w Word -> Word -> Bool
forall a. Ord a => a -> a -> Bool
< Word
10
          then
            case e -> Word -> Word -> Bytes -> Result# e Int#
forall e. e -> Word -> Word -> Bytes -> Result# e Int#
decPosIntMore e
e Word
w (Word
maxIntAsWord Word -> Word -> Word
forall a. Num a => a -> a -> a
+ Word
1) (Int -> Bytes -> Bytes
Bytes.unsafeDrop Int
1 Bytes
chunk0) of
             (# | (# Int#
x, Int#
y, Int#
z #) #) ->
               (# State# s
s0, (# | (# (Int# -> Int#
notI# Int#
x Int# -> Int# -> Int#
+# Int#
1# ), Int#
y, Int#
z #) #) #)
             (# e
err | #) ->
               (# State# s
s0, (# e
err | #) #)
          else (# State# s
s0, (# e
e | #) #)
  else (# State# s
s0, (# e
e | #) #)

decUnsignedIntegerStart ::
     e
  -> Bytes
  -> ST# s (Result# e Integer)
decUnsignedIntegerStart :: e -> Bytes -> ST# s (Result# e Integer)
decUnsignedIntegerStart e
e !Bytes
chunk0 State# s
s0 = if Bytes -> Int
length Bytes
chunk0 Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
0
  then
    let !w :: Word8
w = (ByteArray -> Int -> Word8
forall a. Prim a => ByteArray -> Int -> a
PM.indexByteArray (Bytes -> ByteArray
array Bytes
chunk0) (Bytes -> Int
offset Bytes
chunk0)) Word8 -> Word8 -> Word8
forall a. Num a => a -> a -> a
- Word8
48
     in if Word8
w Word8 -> Word8 -> Bool
forall a. Ord a => a -> a -> Bool
< (Word8
10 :: Word8)
          then
            let !r :: (# Integer, Int#, Int# #)
r = Int -> Int -> Integer -> Bytes -> (# Integer, Int#, Int# #)
decIntegerChunks
                  (Word8 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral @Word8 @Int Word8
w)
                  Int
10
                  Integer
0
                  (Int -> Bytes -> Bytes
Bytes.unsafeDrop Int
1 Bytes
chunk0)
             in (# State# s
s0, (# | (# Integer, Int#, Int# #)
r #) #)
          else (# State# s
s0, (# e
e | #) #)
  else (# State# s
s0, (# e
e | #) #)

-- This will not inline since it is recursive, but worker
-- wrapper will still happen. Fails if the accumulator
-- exceeds the upper bound.
decPosIntMore ::
     e -- Error message
  -> Word -- Accumulator, precondition: less than or equal to bound
  -> Word -- Inclusive Upper Bound, either (2^63 - 1) or 2^63
  -> Bytes -- Chunk
  -> Result# e Int#
decPosIntMore :: e -> Word -> Word -> Bytes -> Result# e Int#
decPosIntMore e
e !Word
acc !Word
upper !Bytes
chunk0 = if Int
len Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
0
  then
    let !w :: Word
w = Word8 -> Word
forall a b. (Integral a, Num b) => a -> b
fromIntegral @Word8 @Word
          (ByteArray -> Int -> Word8
forall a. Prim a => ByteArray -> Int -> a
PM.indexByteArray (Bytes -> ByteArray
array Bytes
chunk0) (Bytes -> Int
offset Bytes
chunk0)) Word -> Word -> Word
forall a. Num a => a -> a -> a
- Word
48
     in if Word
w Word -> Word -> Bool
forall a. Ord a => a -> a -> Bool
< Word
10
          then
            let (Bool
overflow,Word
acc') = Word -> Word -> Word -> (Bool, Word)
positivePushBase10 Word
acc Word
w Word
upper
             in if Bool
overflow
               then (# e
e | #)
               else e -> Word -> Word -> Bytes -> Result# e Int#
forall e. e -> Word -> Word -> Bytes -> Result# e Int#
decPosIntMore e
e Word
acc' Word
upper (Int -> Bytes -> Bytes
Bytes.unsafeDrop Int
1 Bytes
chunk0)
          else (# | (# Int -> Int#
unI (Word -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word
acc), Int -> Int#
unI (Bytes -> Int
offset Bytes
chunk0), Int#
len# #) #)
  else (# | (# Int -> Int#
unI (Word -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word
acc), Int -> Int#
unI (Bytes -> Int
offset Bytes
chunk0), Int#
0# #) #)
  where
  !len :: Int
len@(I# Int#
len# ) = Bytes -> Int
length Bytes
chunk0

-- This will not inline since it is recursive, but worker
-- wrapper will still happen. When the accumulator
-- exceeds the size of a machine integer, this pushes the
-- accumulated machine int and the shift amount onto the
-- stack.
-- We are intentionally lazy in the accumulator. There is
-- no need to force this on every iteration. We do however,
-- force it preemptively every time it changes.
-- Because of how we track overflow, we are able to use the
-- same function for both positive and negative numbers.
decIntegerChunks ::
     Int -- Chunk accumulator (e.g. 236)
  -> Int -- Chunk base-ten bound (e.g. 1000)
  -> Integer -- Accumulator
  -> Bytes -- Chunk
  -> (# Integer, Int#, Int# #)
decIntegerChunks :: Int -> Int -> Integer -> Bytes -> (# Integer, Int#, Int# #)
decIntegerChunks !Int
nAcc !Int
eAcc Integer
acc !Bytes
chunk0 = if Int
len Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
0
  then
    let !w :: Word
w = Word8 -> Word
forall a b. (Integral a, Num b) => a -> b
fromIntegral @Word8 @Word
          (ByteArray -> Int -> Word8
forall a. Prim a => ByteArray -> Int -> a
PM.indexByteArray (Bytes -> ByteArray
array Bytes
chunk0) (Bytes -> Int
offset Bytes
chunk0)) Word -> Word -> Word
forall a. Num a => a -> a -> a
- Word
48
     in if Word
w Word -> Word -> Bool
forall a. Ord a => a -> a -> Bool
< Word
10
          then let !eAcc' :: Int
eAcc' = Int
eAcc Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
10 in
            if Int
eAcc' Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
eAcc
              then Int -> Int -> Integer -> Bytes -> (# Integer, Int#, Int# #)
decIntegerChunks
                (Int
nAcc Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
10 Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Word -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral @Word @Int Word
w)
                Int
eAcc'
                Integer
acc
                (Int -> Bytes -> Bytes
Bytes.unsafeDrop Int
1 Bytes
chunk0)
              else
                -- In this case, notice that we deliberately
                -- unconsume the digit that would have caused
                -- an overflow.
                let !r :: Integer
r = (Integer
acc Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
* Int -> Integer
forall a b. (Integral a, Num b) => a -> b
fromIntegral @Int @Integer Int
eAcc)
                       Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
+ (Int -> Integer
forall a b. (Integral a, Num b) => a -> b
fromIntegral @Int @Integer Int
nAcc)
                 in Int -> Int -> Integer -> Bytes -> (# Integer, Int#, Int# #)
decIntegerChunks Int
0 Int
1 Integer
r Bytes
chunk0
          else
            let !r :: Integer
r = (Integer
acc Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
* Int -> Integer
forall a b. (Integral a, Num b) => a -> b
fromIntegral @Int @Integer Int
eAcc)
                   Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
+ (Int -> Integer
forall a b. (Integral a, Num b) => a -> b
fromIntegral @Int @Integer Int
nAcc)
             in (# Integer
r, Int -> Int#
unI (Bytes -> Int
offset Bytes
chunk0), Int#
len# #)
  else
    let !r :: Integer
r = (Integer
acc Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
* Int -> Integer
forall a b. (Integral a, Num b) => a -> b
fromIntegral @Int @Integer Int
eAcc)
           Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
+ (Int -> Integer
forall a b. (Integral a, Num b) => a -> b
fromIntegral @Int @Integer Int
nAcc)
     in (# Integer
r, Int -> Int#
unI (Bytes -> Int
offset Bytes
chunk0), Int#
0# #)
  where
  !len :: Int
len@(I# Int#
len# ) = Bytes -> Int
length Bytes
chunk0

upcastIntResult :: Result# e Int# -> Result# e Int
upcastIntResult :: Result# e Int# -> Result# e Int
upcastIntResult (# e
e | #) = (# e
e | #)
upcastIntResult (# | (# Int#
a, Int#
b, Int#
c #) #) = (# | (# Int# -> Int
I# Int#
a, Int#
b, Int#
c #) #)

char2Word :: Char -> Word
char2Word :: Char -> Word
char2Word = Int -> Word
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Word) -> (Char -> Int) -> Char -> Word
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> Int
ord

-- | Take characters until the specified character is encountered.
-- Consumes the matched character as well. Fails if the character
-- is not present.  Visually, the cursor advancement and resulting
-- @Bytes@ for @takeTrailedBy \'D\'@ look like this:
--
-- >  A B C D E F | input
-- > |->->->-|    | cursor
-- > {-*-*-}      | result bytes
takeTrailedBy :: e -> Char -> Parser e s Bytes
takeTrailedBy :: e -> Char -> Parser e s Bytes
takeTrailedBy e
e !Char
w = do
  !Int
start <- Parser e s Int
forall e s. Parser e s Int
cursor
  e -> Char -> Parser e s ()
forall e s. e -> Char -> Parser e s ()
skipTrailedBy e
e Char
w
  !Int
end <- Parser e s Int
forall e s. Parser e s Int
cursor
  !ByteArray
arr <- Parser e s ByteArray
forall e s. Parser e s ByteArray
expose
  Bytes -> Parser e s Bytes
forall (f :: * -> *) a. Applicative f => a -> f a
pure (ByteArray -> Int -> Int -> Bytes
Bytes ByteArray
arr Int
start (Int
end Int -> Int -> Int
forall a. Num a => a -> a -> a
- (Int
start Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1)))

-- | Skip all characters until the terminator is encountered
-- and then consume the matching character as well. Visually,
-- @skipTrailedBy \'C\'@ advances the cursor like this:
--
-- >  A Z B Y C X C W
-- > |->->->->-|
--
-- This fails if it reaches the end of input without encountering
-- the character.
skipTrailedBy :: e -> Char -> Parser e s ()
skipTrailedBy :: e -> Char -> Parser e s ()
skipTrailedBy e
e !Char
w = (Bytes -> Result# e ()) -> Parser e s ()
forall e a s. (Bytes -> Result# e a) -> Parser e s a
uneffectful# ((Bytes -> Result# e ()) -> Parser e s ())
-> (Bytes -> Result# e ()) -> Parser e s ()
forall a b. (a -> b) -> a -> b
$ \Bytes
c ->
  e -> Char -> Bytes -> Result# e ()
forall e. e -> Char -> Bytes -> Result# e ()
skipUntilConsumeLoop e
e Char
w Bytes
c

-- | Skip all characters until the terminator is encountered.
-- This does not consume the terminator. Visually, @skipUntil \'C\'@
-- advances the cursor like this:
--
-- >  A Z B Y C X C W
-- > |->->->-|
--
-- This succeeds if it reaches the end of the input without
-- encountering the terminator. It never fails.
skipUntil :: Char -> Parser e s ()
skipUntil :: Char -> Parser e s ()
skipUntil !Char
w = (Bytes -> Result# e ()) -> Parser e s ()
forall e a s. (Bytes -> Result# e a) -> Parser e s a
uneffectful# ((Bytes -> Result# e ()) -> Parser e s ())
-> (Bytes -> Result# e ()) -> Parser e s ()
forall a b. (a -> b) -> a -> b
$ \Bytes
c -> Char -> Bytes -> Result# e ()
forall e. Char -> Bytes -> Result# e ()
skipUntilLoop Char
w Bytes
c

skipUntilLoop ::
     Char -- byte to match
  -> Bytes -- Chunk
  -> Result# e ()
skipUntilLoop :: Char -> Bytes -> Result# e ()
skipUntilLoop !Char
w !Bytes
c = case Bytes -> Int
length Bytes
c of
  Int
0 -> (# | (# (), Int -> Int#
unI (Bytes -> Int
offset Bytes
c), Int#
0# #) #)
  Int
_ -> if ByteArray -> Int -> Char
indexLatinCharArray (Bytes -> ByteArray
array Bytes
c) (Bytes -> Int
offset Bytes
c) Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
/= Char
w
    then Char -> Bytes -> Result# e ()
forall e. Char -> Bytes -> Result# e ()
skipUntilLoop Char
w (Int -> Bytes -> Bytes
Bytes.unsafeDrop Int
1 Bytes
c)
    else (# | (# (), Int -> Int#
unI (Bytes -> Int
offset Bytes
c), Int -> Int#
unI (Bytes -> Int
length Bytes
c) #) #)

skipUntilConsumeLoop ::
     e -- Error message
  -> Char -- byte to match
  -> Bytes -- Chunk
  -> Result# e ()
skipUntilConsumeLoop :: e -> Char -> Bytes -> Result# e ()
skipUntilConsumeLoop e
e !Char
w !Bytes
c = case Bytes -> Int
length Bytes
c of
  Int
0 -> (# e
e | #)
  Int
_ -> if ByteArray -> Int -> Char
indexLatinCharArray (Bytes -> ByteArray
array Bytes
c) (Bytes -> Int
offset Bytes
c) Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
/= Char
w
    then e -> Char -> Bytes -> Result# e ()
forall e. e -> Char -> Bytes -> Result# e ()
skipUntilConsumeLoop e
e Char
w (Int -> Bytes -> Bytes
Bytes.unsafeDrop Int
1 Bytes
c)
    else (# | (# (), Int -> Int#
unI (Bytes -> Int
offset Bytes
c Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1), Int -> Int#
unI (Bytes -> Int
length Bytes
c Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1) #) #)


-- | Parse exactly eight ASCII-encoded characters, interpreting them as the
-- hexadecimal encoding of a 32-bit number. Note that this rejects a sequence
-- such as @BC5A9@, requiring @000BC5A9@ instead. This is insensitive to case.
hexFixedWord32 :: e -> Parser e s Word32
{-# inline hexFixedWord32 #-}
hexFixedWord32 :: e -> Parser e s Word32
hexFixedWord32 e
e = ((# ByteArray#, Int#, Int# #) -> ST# s (Result# e Word32))
-> Parser e s Word32
forall e s a.
((# ByteArray#, Int#, Int# #) -> ST# s (Result# e a))
-> Parser e s a
Parser
  (\(# ByteArray#, Int#, Int# #)
x State# s
s0 -> case Parser e s Word#
-> (# ByteArray#, Int#, Int# #) -> ST# s (Result# e Word#)
forall e s a.
Parser e s a -> (# ByteArray#, Int#, Int# #) -> ST# s (Result# e a)
runParser (e -> Parser e s Word#
forall e s. e -> Parser e s Word#
hexFixedWord32# e
e) (# ByteArray#, Int#, Int# #)
x State# s
s0 of
    (# State# s
s1, Result# e Word#
r #) -> case Result# e Word#
r of
      (# e
err | #) -> (# State# s
s1, (# e
err | #) #)
      (# | (# Word#
a, Int#
b, Int#
c #) #) -> (# State# s
s1, (# | (# Word# -> Word32
W32# (
#if MIN_VERSION_base(4,16,0)
        Exts.wordToWord32#
#endif
        Word#
a), Int#
b, Int#
c #) #) #)
  )

hexFixedWord32# :: e -> Parser e s Word#
{-# noinline hexFixedWord32# #-}
hexFixedWord32# :: e -> Parser e s Word#
hexFixedWord32# e
e = (Bytes -> Result# e Word#) -> Parser e s Word#
forall e s. (Bytes -> Result# e Word#) -> Parser e s Word#
uneffectfulWord# ((Bytes -> Result# e Word#) -> Parser e s Word#)
-> (Bytes -> Result# e Word#) -> Parser e s Word#
forall a b. (a -> b) -> a -> b
$ \Bytes
chunk -> if Bytes -> Int
length Bytes
chunk Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
8
  then
    let !w0 :: Word
w0@(W# Word#
n0) = Word8 -> Word
oneHex (Word8 -> Word) -> Word8 -> Word
forall a b. (a -> b) -> a -> b
$ ByteArray -> Int -> Word8
forall a. Prim a => ByteArray -> Int -> a
PM.indexByteArray (Bytes -> ByteArray
array Bytes
chunk) (Bytes -> Int
offset Bytes
chunk)
        !w1 :: Word
w1@(W# Word#
n1) = Word8 -> Word
oneHex (Word8 -> Word) -> Word8 -> Word
forall a b. (a -> b) -> a -> b
$ ByteArray -> Int -> Word8
forall a. Prim a => ByteArray -> Int -> a
PM.indexByteArray (Bytes -> ByteArray
array Bytes
chunk) (Bytes -> Int
offset Bytes
chunk Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1)
        !w2 :: Word
w2@(W# Word#
n2) = Word8 -> Word
oneHex (Word8 -> Word) -> Word8 -> Word
forall a b. (a -> b) -> a -> b
$ ByteArray -> Int -> Word8
forall a. Prim a => ByteArray -> Int -> a
PM.indexByteArray (Bytes -> ByteArray
array Bytes
chunk) (Bytes -> Int
offset Bytes
chunk Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
2)
        !w3 :: Word
w3@(W# Word#
n3) = Word8 -> Word
oneHex (Word8 -> Word) -> Word8 -> Word
forall a b. (a -> b) -> a -> b
$ ByteArray -> Int -> Word8
forall a. Prim a => ByteArray -> Int -> a
PM.indexByteArray (Bytes -> ByteArray
array Bytes
chunk) (Bytes -> Int
offset Bytes
chunk Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
3)
        !w4 :: Word
w4@(W# Word#
n4) = Word8 -> Word
oneHex (Word8 -> Word) -> Word8 -> Word
forall a b. (a -> b) -> a -> b
$ ByteArray -> Int -> Word8
forall a. Prim a => ByteArray -> Int -> a
PM.indexByteArray (Bytes -> ByteArray
array Bytes
chunk) (Bytes -> Int
offset Bytes
chunk Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
4)
        !w5 :: Word
w5@(W# Word#
n5) = Word8 -> Word
oneHex (Word8 -> Word) -> Word8 -> Word
forall a b. (a -> b) -> a -> b
$ ByteArray -> Int -> Word8
forall a. Prim a => ByteArray -> Int -> a
PM.indexByteArray (Bytes -> ByteArray
array Bytes
chunk) (Bytes -> Int
offset Bytes
chunk Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
5)
        !w6 :: Word
w6@(W# Word#
n6) = Word8 -> Word
oneHex (Word8 -> Word) -> Word8 -> Word
forall a b. (a -> b) -> a -> b
$ ByteArray -> Int -> Word8
forall a. Prim a => ByteArray -> Int -> a
PM.indexByteArray (Bytes -> ByteArray
array Bytes
chunk) (Bytes -> Int
offset Bytes
chunk Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
6)
        !w7 :: Word
w7@(W# Word#
n7) = Word8 -> Word
oneHex (Word8 -> Word) -> Word8 -> Word
forall a b. (a -> b) -> a -> b
$ ByteArray -> Int -> Word8
forall a. Prim a => ByteArray -> Int -> a
PM.indexByteArray (Bytes -> ByteArray
array Bytes
chunk) (Bytes -> Int
offset Bytes
chunk Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
7)
     in if | Word
w0 Word -> Word -> Word
forall a. Bits a => a -> a -> a
.|. Word
w1 Word -> Word -> Word
forall a. Bits a => a -> a -> a
.|. Word
w2 Word -> Word -> Word
forall a. Bits a => a -> a -> a
.|. Word
w3 Word -> Word -> Word
forall a. Bits a => a -> a -> a
.|. Word
w4 Word -> Word -> Word
forall a. Bits a => a -> a -> a
.|. Word
w5 Word -> Word -> Word
forall a. Bits a => a -> a -> a
.|. Word
w6 Word -> Word -> Word
forall a. Bits a => a -> a -> a
.|. Word
w7 Word -> Word -> Bool
forall a. Eq a => a -> a -> Bool
/= Word
forall a. Bounded a => a
maxBound ->
             (# |
                (# (Word#
n0 Word# -> Word# -> Word#
`Exts.timesWord#` Word#
268435456##) Word# -> Word# -> Word#
`Exts.plusWord#`
                   (Word#
n1 Word# -> Word# -> Word#
`Exts.timesWord#` Word#
16777216##) Word# -> Word# -> Word#
`Exts.plusWord#`
                   (Word#
n2 Word# -> Word# -> Word#
`Exts.timesWord#` Word#
1048576##) Word# -> Word# -> Word#
`Exts.plusWord#`
                   (Word#
n3 Word# -> Word# -> Word#
`Exts.timesWord#` Word#
65536##) Word# -> Word# -> Word#
`Exts.plusWord#`
                   (Word#
n4 Word# -> Word# -> Word#
`Exts.timesWord#` Word#
4096##) Word# -> Word# -> Word#
`Exts.plusWord#`
                   (Word#
n5 Word# -> Word# -> Word#
`Exts.timesWord#` Word#
256##) Word# -> Word# -> Word#
`Exts.plusWord#`
                   (Word#
n6 Word# -> Word# -> Word#
`Exts.timesWord#` Word#
16##) Word# -> Word# -> Word#
`Exts.plusWord#`
                   Word#
n7
                ,  Int -> Int#
unI (Bytes -> Int
offset Bytes
chunk) Int# -> Int# -> Int#
+# Int#
8#
                ,  Int -> Int#
unI (Bytes -> Int
length Bytes
chunk) Int# -> Int# -> Int#
-# Int#
8# #) #)
           | Bool
otherwise -> (# e
e | #)
  else (# e
e | #)

-- | Parse exactly 16 ASCII-encoded characters, interpreting them as the
-- hexadecimal encoding of a 64-bit number. Note that this rejects a sequence
-- such as @BC5A9@, requiring @00000000000BC5A9@ instead. This is insensitive
-- to case.
hexFixedWord64 :: e -> Parser e s Word64
{-# inline hexFixedWord64 #-}
hexFixedWord64 :: e -> Parser e s Word64
hexFixedWord64 e
e = ((# ByteArray#, Int#, Int# #) -> ST# s (Result# e Word64))
-> Parser e s Word64
forall e s a.
((# ByteArray#, Int#, Int# #) -> ST# s (Result# e a))
-> Parser e s a
Parser
  (\(# ByteArray#, Int#, Int# #)
x State# s
s0 -> case Parser e s Word#
-> (# ByteArray#, Int#, Int# #) -> ST# s (Result# e Word#)
forall e s a.
Parser e s a -> (# ByteArray#, Int#, Int# #) -> ST# s (Result# e a)
runParser (e -> Parser e s Word#
forall e s. e -> Parser e s Word#
hexFixedWord64# e
e) (# ByteArray#, Int#, Int# #)
x State# s
s0 of
    (# State# s
s1, Result# e Word#
r #) -> case Result# e Word#
r of
      (# e
err | #) -> (# State# s
s1, (# e
err | #) #)
      (# | (# Word#
a, Int#
b, Int#
c #) #) -> (# State# s
s1, (# | (# Word# -> Word64
W64# Word#
a, Int#
b, Int#
c #) #) #)
  )

hexFixedWord64# :: e -> Parser e s Word#
{-# noinline hexFixedWord64# #-}
hexFixedWord64# :: e -> Parser e s Word#
hexFixedWord64# e
e = (Bytes -> Result# e Word#) -> Parser e s Word#
forall e s. (Bytes -> Result# e Word#) -> Parser e s Word#
uneffectfulWord# ((Bytes -> Result# e Word#) -> Parser e s Word#)
-> (Bytes -> Result# e Word#) -> Parser e s Word#
forall a b. (a -> b) -> a -> b
$ \Bytes
chunk -> if Bytes -> Int
length Bytes
chunk Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
16
  then
    let go :: Int -> t -> Word -> Result# e Word#
go !Int
off !t
len !Word
acc = case t
len of
          t
0 -> case Word
acc of
            W# Word#
r ->
              (# | (# Word#
r
              ,  Int -> Int#
unI Int
off
              ,  Int -> Int#
unI (Bytes -> Int
length Bytes
chunk) Int# -> Int# -> Int#
-# Int#
16# #) #)
          t
_ -> case Word8 -> Maybe Word
oneHexMaybe (ByteArray -> Int -> Word8
forall a. Prim a => ByteArray -> Int -> a
PM.indexByteArray (Bytes -> ByteArray
array Bytes
chunk) Int
off) of
            Maybe Word
Nothing -> (# e
e | #)
            Just Word
w -> Int -> t -> Word -> Result# e Word#
go (Int
off Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1) (t
len t -> t -> t
forall a. Num a => a -> a -> a
- t
1) ((Word
acc Word -> Word -> Word
forall a. Num a => a -> a -> a
* Word
16) Word -> Word -> Word
forall a. Num a => a -> a -> a
+ Word
w)
     in Int -> Int -> Word -> Result# e Word#
forall t. (Eq t, Num t) => Int -> t -> Word -> Result# e Word#
go (Bytes -> Int
offset Bytes
chunk) (Int
16 :: Int) (Word
0 :: Word)
  else (# e
e | #)

-- | Parse exactly four ASCII-encoded characters, interpreting
-- them as the hexadecimal encoding of a 16-bit number. Note that
-- this rejects a sequence such as @5A9@, requiring @05A9@ instead.
-- This is insensitive to case. This is particularly useful when
-- parsing escape sequences in C or JSON, which allow encoding
-- characters in the Basic Multilingual Plane as @\\uhhhh@.
hexFixedWord16 :: e -> Parser e s Word16
{-# inline hexFixedWord16 #-}
hexFixedWord16 :: e -> Parser e s Word16
hexFixedWord16 e
e = ((# ByteArray#, Int#, Int# #) -> ST# s (Result# e Word16))
-> Parser e s Word16
forall e s a.
((# ByteArray#, Int#, Int# #) -> ST# s (Result# e a))
-> Parser e s a
Parser
  (\(# ByteArray#, Int#, Int# #)
x State# s
s0 -> case Parser e s Word#
-> (# ByteArray#, Int#, Int# #) -> ST# s (Result# e Word#)
forall e s a.
Parser e s a -> (# ByteArray#, Int#, Int# #) -> ST# s (Result# e a)
runParser (e -> Parser e s Word#
forall e s. e -> Parser e s Word#
hexFixedWord16# e
e) (# ByteArray#, Int#, Int# #)
x State# s
s0 of
    (# State# s
s1, Result# e Word#
r #) -> case Result# e Word#
r of
      (# e
err | #) -> (# State# s
s1, (# e
err | #) #)
      (# | (# Word#
a, Int#
b, Int#
c #) #) -> (# State# s
s1, (# | (# Word# -> Word16
W16# (
#if MIN_VERSION_base(4,16,0)
        Exts.wordToWord16#
#endif
        Word#
a), Int#
b, Int#
c #) #) #)
  )

hexFixedWord16# :: e -> Parser e s Word#
{-# noinline hexFixedWord16# #-}
hexFixedWord16# :: e -> Parser e s Word#
hexFixedWord16# e
e = (Bytes -> Result# e Word#) -> Parser e s Word#
forall e s. (Bytes -> Result# e Word#) -> Parser e s Word#
uneffectfulWord# ((Bytes -> Result# e Word#) -> Parser e s Word#)
-> (Bytes -> Result# e Word#) -> Parser e s Word#
forall a b. (a -> b) -> a -> b
$ \Bytes
chunk -> if Bytes -> Int
length Bytes
chunk Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
4
  then
    let !w0 :: Word
w0@(W# Word#
n0) = Word8 -> Word
oneHex (Word8 -> Word) -> Word8 -> Word
forall a b. (a -> b) -> a -> b
$ ByteArray -> Int -> Word8
forall a. Prim a => ByteArray -> Int -> a
PM.indexByteArray (Bytes -> ByteArray
array Bytes
chunk) (Bytes -> Int
offset Bytes
chunk)
        !w1 :: Word
w1@(W# Word#
n1) = Word8 -> Word
oneHex (Word8 -> Word) -> Word8 -> Word
forall a b. (a -> b) -> a -> b
$ ByteArray -> Int -> Word8
forall a. Prim a => ByteArray -> Int -> a
PM.indexByteArray (Bytes -> ByteArray
array Bytes
chunk) (Bytes -> Int
offset Bytes
chunk Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1)
        !w2 :: Word
w2@(W# Word#
n2) = Word8 -> Word
oneHex (Word8 -> Word) -> Word8 -> Word
forall a b. (a -> b) -> a -> b
$ ByteArray -> Int -> Word8
forall a. Prim a => ByteArray -> Int -> a
PM.indexByteArray (Bytes -> ByteArray
array Bytes
chunk) (Bytes -> Int
offset Bytes
chunk Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
2)
        !w3 :: Word
w3@(W# Word#
n3) = Word8 -> Word
oneHex (Word8 -> Word) -> Word8 -> Word
forall a b. (a -> b) -> a -> b
$ ByteArray -> Int -> Word8
forall a. Prim a => ByteArray -> Int -> a
PM.indexByteArray (Bytes -> ByteArray
array Bytes
chunk) (Bytes -> Int
offset Bytes
chunk Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
3)
     in if | Word
w0 Word -> Word -> Word
forall a. Bits a => a -> a -> a
.|. Word
w1 Word -> Word -> Word
forall a. Bits a => a -> a -> a
.|. Word
w2 Word -> Word -> Word
forall a. Bits a => a -> a -> a
.|. Word
w3 Word -> Word -> Bool
forall a. Eq a => a -> a -> Bool
/= Word
forall a. Bounded a => a
maxBound ->
             (# |
                (# (Word#
n0 Word# -> Word# -> Word#
`Exts.timesWord#` Word#
4096##) Word# -> Word# -> Word#
`Exts.plusWord#`
                   (Word#
n1 Word# -> Word# -> Word#
`Exts.timesWord#` Word#
256##) Word# -> Word# -> Word#
`Exts.plusWord#`
                   (Word#
n2 Word# -> Word# -> Word#
`Exts.timesWord#` Word#
16##) Word# -> Word# -> Word#
`Exts.plusWord#`
                   Word#
n3
                ,  Int -> Int#
unI (Bytes -> Int
offset Bytes
chunk) Int# -> Int# -> Int#
+# Int#
4#
                ,  Int -> Int#
unI (Bytes -> Int
length Bytes
chunk) Int# -> Int# -> Int#
-# Int#
4# #) #)
           | Bool
otherwise -> (# e
e | #)
  else (# e
e | #)

-- | Parse exactly two ASCII-encoded characters, interpretting
-- them as the hexadecimal encoding of a 8-bit number. Note that
-- this rejects a sequence such as @A@, requiring @0A@ instead.
-- This is insensitive to case.
hexFixedWord8 :: e -> Parser e s Word8
{-# inline hexFixedWord8 #-}
hexFixedWord8 :: e -> Parser e s Word8
hexFixedWord8 e
e = ((# ByteArray#, Int#, Int# #) -> ST# s (Result# e Word8))
-> Parser e s Word8
forall e s a.
((# ByteArray#, Int#, Int# #) -> ST# s (Result# e a))
-> Parser e s a
Parser
  (\(# ByteArray#, Int#, Int# #)
x State# s
s0 -> case Parser e s Word#
-> (# ByteArray#, Int#, Int# #) -> ST# s (Result# e Word#)
forall e s a.
Parser e s a -> (# ByteArray#, Int#, Int# #) -> ST# s (Result# e a)
runParser (e -> Parser e s Word#
forall e s. e -> Parser e s Word#
hexFixedWord8# e
e) (# ByteArray#, Int#, Int# #)
x State# s
s0 of
    (# State# s
s1, Result# e Word#
r #) -> case Result# e Word#
r of
      (# e
err | #) -> (# State# s
s1, (# e
err | #) #)
      (# | (# Word#
a, Int#
b, Int#
c #) #) -> (# State# s
s1, (# | (# Word# -> Word8
W8# (
#if MIN_VERSION_base(4,16,0)
        Exts.wordToWord8#
#endif
        Word#
a), Int#
b, Int#
c #) #) #)
  )

hexFixedWord8# :: e -> Parser e s Word#
{-# noinline hexFixedWord8# #-}
hexFixedWord8# :: e -> Parser e s Word#
hexFixedWord8# e
e = (Bytes -> Result# e Word#) -> Parser e s Word#
forall e s. (Bytes -> Result# e Word#) -> Parser e s Word#
uneffectfulWord# ((Bytes -> Result# e Word#) -> Parser e s Word#)
-> (Bytes -> Result# e Word#) -> Parser e s Word#
forall a b. (a -> b) -> a -> b
$ \Bytes
chunk -> if Bytes -> Int
length Bytes
chunk Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
2
  then
    let !w0 :: Word
w0@(W# Word#
n0) = Word8 -> Word
oneHex (Word8 -> Word) -> Word8 -> Word
forall a b. (a -> b) -> a -> b
$ ByteArray -> Int -> Word8
forall a. Prim a => ByteArray -> Int -> a
PM.indexByteArray (Bytes -> ByteArray
array Bytes
chunk) (Bytes -> Int
offset Bytes
chunk)
        !w1 :: Word
w1@(W# Word#
n1) = Word8 -> Word
oneHex (Word8 -> Word) -> Word8 -> Word
forall a b. (a -> b) -> a -> b
$ ByteArray -> Int -> Word8
forall a. Prim a => ByteArray -> Int -> a
PM.indexByteArray (Bytes -> ByteArray
array Bytes
chunk) (Bytes -> Int
offset Bytes
chunk Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1)
     in if | Word
w0 Word -> Word -> Word
forall a. Bits a => a -> a -> a
.|. Word
w1 Word -> Word -> Bool
forall a. Eq a => a -> a -> Bool
/= Word
forall a. Bounded a => a
maxBound ->
             (# |
                (# (Word#
n0 Word# -> Word# -> Word#
`Exts.timesWord#` Word#
16##) Word# -> Word# -> Word#
`Exts.plusWord#`
                   Word#
n1
                ,  Int -> Int#
unI (Bytes -> Int
offset Bytes
chunk) Int# -> Int# -> Int#
+# Int#
2#
                ,  Int -> Int#
unI (Bytes -> Int
length Bytes
chunk) Int# -> Int# -> Int#
-# Int#
2# #) #)
           | Bool
otherwise -> (# e
e | #)
  else (# e
e | #)

-- | Consume a single character that is the lowercase hexadecimal
-- encoding of a 4-bit word. Fails if the character is not in the class
-- @[a-f0-9]@.
hexNibbleLower :: e -> Parser e s Word
hexNibbleLower :: e -> Parser e s Word
hexNibbleLower e
e = (Bytes -> Result e Word) -> Parser e s Word
forall e a s. (Bytes -> Result e a) -> Parser e s a
uneffectful ((Bytes -> Result e Word) -> Parser e s Word)
-> (Bytes -> Result e Word) -> Parser e s Word
forall a b. (a -> b) -> a -> b
$ \Bytes
chunk -> case Bytes -> Int
length Bytes
chunk of
  Int
0 -> e -> Result e Word
forall e a. e -> Result e a
Failure e
e
  Int
_ ->
    let w :: Word8
w = ByteArray -> Int -> Word8
forall a. Prim a => ByteArray -> Int -> a
PM.indexByteArray (Bytes -> ByteArray
array Bytes
chunk) (Bytes -> Int
offset Bytes
chunk) :: Word8 in
    if | Word8
w Word8 -> Word8 -> Bool
forall a. Ord a => a -> a -> Bool
>= Word8
48 Bool -> Bool -> Bool
&& Word8
w Word8 -> Word8 -> Bool
forall a. Ord a => a -> a -> Bool
< Word8
58 -> Word -> Int -> Int -> Result e Word
forall e a. a -> Int -> Int -> Result e a
Success (Word8 -> Word
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word8
w Word -> Word -> Word
forall a. Num a => a -> a -> a
- Word
48) (Bytes -> Int
offset Bytes
chunk Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1) (Bytes -> Int
length Bytes
chunk Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1)
       | Word8
w Word8 -> Word8 -> Bool
forall a. Ord a => a -> a -> Bool
>= Word8
97 Bool -> Bool -> Bool
&& Word8
w Word8 -> Word8 -> Bool
forall a. Ord a => a -> a -> Bool
< Word8
103 -> Word -> Int -> Int -> Result e Word
forall e a. a -> Int -> Int -> Result e a
Success (Word8 -> Word
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word8
w Word -> Word -> Word
forall a. Num a => a -> a -> a
- Word
87) (Bytes -> Int
offset Bytes
chunk Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1) (Bytes -> Int
length Bytes
chunk Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1)
       | Bool
otherwise -> e -> Result e Word
forall e a. e -> Result e a
Failure e
e

-- | Consume a single character that is the case-insensitive hexadecimal
-- encoding of a 4-bit word. Fails if the character is not in the class
-- @[a-fA-F0-9]@.
hexNibble :: e -> Parser e s Word
hexNibble :: e -> Parser e s Word
hexNibble e
e = (Bytes -> Result e Word) -> Parser e s Word
forall e a s. (Bytes -> Result e a) -> Parser e s a
uneffectful ((Bytes -> Result e Word) -> Parser e s Word)
-> (Bytes -> Result e Word) -> Parser e s Word
forall a b. (a -> b) -> a -> b
$ \Bytes
chunk -> case Bytes -> Int
length Bytes
chunk of
  Int
0 -> e -> Result e Word
forall e a. e -> Result e a
Failure e
e
  Int
_ ->
    let w :: Word8
w = ByteArray -> Int -> Word8
forall a. Prim a => ByteArray -> Int -> a
PM.indexByteArray (Bytes -> ByteArray
array Bytes
chunk) (Bytes -> Int
offset Bytes
chunk) :: Word8 in
    if | Word8
w Word8 -> Word8 -> Bool
forall a. Ord a => a -> a -> Bool
>= Word8
48 Bool -> Bool -> Bool
&& Word8
w Word8 -> Word8 -> Bool
forall a. Ord a => a -> a -> Bool
< Word8
58 -> Word -> Int -> Int -> Result e Word
forall e a. a -> Int -> Int -> Result e a
Success (Word8 -> Word
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word8
w Word -> Word -> Word
forall a. Num a => a -> a -> a
- Word
48) (Bytes -> Int
offset Bytes
chunk Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1) (Bytes -> Int
length Bytes
chunk Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1)
       | Word8
w Word8 -> Word8 -> Bool
forall a. Ord a => a -> a -> Bool
>= Word8
65 Bool -> Bool -> Bool
&& Word8
w Word8 -> Word8 -> Bool
forall a. Ord a => a -> a -> Bool
< Word8
71 -> Word -> Int -> Int -> Result e Word
forall e a. a -> Int -> Int -> Result e a
Success (Word8 -> Word
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word8
w Word -> Word -> Word
forall a. Num a => a -> a -> a
- Word
55) (Bytes -> Int
offset Bytes
chunk Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1) (Bytes -> Int
length Bytes
chunk Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1)
       | Word8
w Word8 -> Word8 -> Bool
forall a. Ord a => a -> a -> Bool
>= Word8
97 Bool -> Bool -> Bool
&& Word8
w Word8 -> Word8 -> Bool
forall a. Ord a => a -> a -> Bool
< Word8
103 -> Word -> Int -> Int -> Result e Word
forall e a. a -> Int -> Int -> Result e a
Success (Word8 -> Word
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word8
w Word -> Word -> Word
forall a. Num a => a -> a -> a
- Word
87) (Bytes -> Int
offset Bytes
chunk Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1) (Bytes -> Int
length Bytes
chunk Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1)
       | Bool
otherwise -> e -> Result e Word
forall e a. e -> Result e a
Failure e
e

-- | Consume a single character that is the lowercase hexadecimal
-- encoding of a 4-bit word. Returns @Nothing@ without consuming
-- the character if it is not in the class @[a-f0-9]@. The parser
-- never fails.
tryHexNibbleLower :: Parser e s (Maybe Word)
tryHexNibbleLower :: Parser e s (Maybe Word)
tryHexNibbleLower = (Bytes -> InternalStep (Maybe Word)) -> Parser e s (Maybe Word)
forall a e s. (Bytes -> InternalStep a) -> Parser e s a
unfailing ((Bytes -> InternalStep (Maybe Word)) -> Parser e s (Maybe Word))
-> (Bytes -> InternalStep (Maybe Word)) -> Parser e s (Maybe Word)
forall a b. (a -> b) -> a -> b
$ \Bytes
chunk -> case Bytes -> Int
length Bytes
chunk of
  Int
0 -> Maybe Word -> Int -> Int -> InternalStep (Maybe Word)
forall a. a -> Int -> Int -> InternalStep a
InternalStep Maybe Word
forall a. Maybe a
Nothing (Bytes -> Int
offset Bytes
chunk) (Bytes -> Int
length Bytes
chunk)
  Int
_ ->
    let w :: Word8
w = ByteArray -> Int -> Word8
forall a. Prim a => ByteArray -> Int -> a
PM.indexByteArray (Bytes -> ByteArray
array Bytes
chunk) (Bytes -> Int
offset Bytes
chunk) :: Word8 in
    if | Word8
w Word8 -> Word8 -> Bool
forall a. Ord a => a -> a -> Bool
>= Word8
48 Bool -> Bool -> Bool
&& Word8
w Word8 -> Word8 -> Bool
forall a. Ord a => a -> a -> Bool
< Word8
58 -> Maybe Word -> Int -> Int -> InternalStep (Maybe Word)
forall a. a -> Int -> Int -> InternalStep a
InternalStep (Word -> Maybe Word
forall a. a -> Maybe a
Just (Word8 -> Word
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word8
w Word -> Word -> Word
forall a. Num a => a -> a -> a
- Word
48)) (Bytes -> Int
offset Bytes
chunk Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1) (Bytes -> Int
length Bytes
chunk Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1)
       | Word8
w Word8 -> Word8 -> Bool
forall a. Ord a => a -> a -> Bool
>= Word8
97 Bool -> Bool -> Bool
&& Word8
w Word8 -> Word8 -> Bool
forall a. Ord a => a -> a -> Bool
< Word8
103 -> Maybe Word -> Int -> Int -> InternalStep (Maybe Word)
forall a. a -> Int -> Int -> InternalStep a
InternalStep (Word -> Maybe Word
forall a. a -> Maybe a
Just (Word8 -> Word
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word8
w Word -> Word -> Word
forall a. Num a => a -> a -> a
- Word
87)) (Bytes -> Int
offset Bytes
chunk Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1) (Bytes -> Int
length Bytes
chunk Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1)
       | Bool
otherwise -> Maybe Word -> Int -> Int -> InternalStep (Maybe Word)
forall a. a -> Int -> Int -> InternalStep a
InternalStep Maybe Word
forall a. Maybe a
Nothing (Bytes -> Int
offset Bytes
chunk) (Bytes -> Int
length Bytes
chunk)

-- | Consume a single character that is the case-insensitive hexadecimal
-- encoding of a 4-bit word. Returns @Nothing@ without consuming
-- the character if it is not in the class @[a-fA-F0-9]@. This parser
-- never fails.
tryHexNibble :: Parser e s (Maybe Word)
tryHexNibble :: Parser e s (Maybe Word)
tryHexNibble = (Bytes -> InternalStep (Maybe Word)) -> Parser e s (Maybe Word)
forall a e s. (Bytes -> InternalStep a) -> Parser e s a
unfailing ((Bytes -> InternalStep (Maybe Word)) -> Parser e s (Maybe Word))
-> (Bytes -> InternalStep (Maybe Word)) -> Parser e s (Maybe Word)
forall a b. (a -> b) -> a -> b
$ \Bytes
chunk -> case Bytes -> Int
length Bytes
chunk of
  Int
0 -> Maybe Word -> Int -> Int -> InternalStep (Maybe Word)
forall a. a -> Int -> Int -> InternalStep a
InternalStep Maybe Word
forall a. Maybe a
Nothing (Bytes -> Int
offset Bytes
chunk) (Bytes -> Int
length Bytes
chunk)
  Int
_ ->
    let w :: Word8
w = ByteArray -> Int -> Word8
forall a. Prim a => ByteArray -> Int -> a
PM.indexByteArray (Bytes -> ByteArray
array Bytes
chunk) (Bytes -> Int
offset Bytes
chunk) :: Word8 in
    if | Word8
w Word8 -> Word8 -> Bool
forall a. Ord a => a -> a -> Bool
>= Word8
48 Bool -> Bool -> Bool
&& Word8
w Word8 -> Word8 -> Bool
forall a. Ord a => a -> a -> Bool
< Word8
58 -> Maybe Word -> Int -> Int -> InternalStep (Maybe Word)
forall a. a -> Int -> Int -> InternalStep a
InternalStep (Word -> Maybe Word
forall a. a -> Maybe a
Just (Word8 -> Word
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word8
w Word -> Word -> Word
forall a. Num a => a -> a -> a
- Word
48)) (Bytes -> Int
offset Bytes
chunk Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1) (Bytes -> Int
length Bytes
chunk Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1)
       | Word8
w Word8 -> Word8 -> Bool
forall a. Ord a => a -> a -> Bool
>= Word8
65 Bool -> Bool -> Bool
&& Word8
w Word8 -> Word8 -> Bool
forall a. Ord a => a -> a -> Bool
< Word8
71 -> Maybe Word -> Int -> Int -> InternalStep (Maybe Word)
forall a. a -> Int -> Int -> InternalStep a
InternalStep (Word -> Maybe Word
forall a. a -> Maybe a
Just (Word8 -> Word
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word8
w Word -> Word -> Word
forall a. Num a => a -> a -> a
- Word
55)) (Bytes -> Int
offset Bytes
chunk Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1) (Bytes -> Int
length Bytes
chunk Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1)
       | Word8
w Word8 -> Word8 -> Bool
forall a. Ord a => a -> a -> Bool
>= Word8
97 Bool -> Bool -> Bool
&& Word8
w Word8 -> Word8 -> Bool
forall a. Ord a => a -> a -> Bool
< Word8
103 -> Maybe Word -> Int -> Int -> InternalStep (Maybe Word)
forall a. a -> Int -> Int -> InternalStep a
InternalStep (Word -> Maybe Word
forall a. a -> Maybe a
Just (Word8 -> Word
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word8
w Word -> Word -> Word
forall a. Num a => a -> a -> a
- Word
87)) (Bytes -> Int
offset Bytes
chunk Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1) (Bytes -> Int
length Bytes
chunk Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1)
       | Bool
otherwise -> Maybe Word -> Int -> Int -> InternalStep (Maybe Word)
forall a. a -> Int -> Int -> InternalStep a
InternalStep Maybe Word
forall a. Maybe a
Nothing (Bytes -> Int
offset Bytes
chunk) (Bytes -> Int
length Bytes
chunk)

-- Returns the maximum machine word if the argument is not
-- the ASCII encoding of a hexadecimal digit.
oneHex :: Word8 -> Word
{-# inline oneHex #-}
oneHex :: Word8 -> Word
oneHex Word8
w
  | Word8
w Word8 -> Word8 -> Bool
forall a. Ord a => a -> a -> Bool
>= Word8
48 Bool -> Bool -> Bool
&& Word8
w Word8 -> Word8 -> Bool
forall a. Ord a => a -> a -> Bool
< Word8
58 = (Word8 -> Word
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word8
w Word -> Word -> Word
forall a. Num a => a -> a -> a
- Word
48)
  | Word8
w Word8 -> Word8 -> Bool
forall a. Ord a => a -> a -> Bool
>= Word8
65 Bool -> Bool -> Bool
&& Word8
w Word8 -> Word8 -> Bool
forall a. Ord a => a -> a -> Bool
< Word8
71 = (Word8 -> Word
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word8
w Word -> Word -> Word
forall a. Num a => a -> a -> a
- Word
55)
  | Word8
w Word8 -> Word8 -> Bool
forall a. Ord a => a -> a -> Bool
>= Word8
97 Bool -> Bool -> Bool
&& Word8
w Word8 -> Word8 -> Bool
forall a. Ord a => a -> a -> Bool
< Word8
103 = (Word8 -> Word
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word8
w Word -> Word -> Word
forall a. Num a => a -> a -> a
- Word
87)
  | Bool
otherwise = Word
forall a. Bounded a => a
maxBound

oneHexMaybe :: Word8 -> Maybe Word
{-# inline oneHexMaybe #-}
oneHexMaybe :: Word8 -> Maybe Word
oneHexMaybe Word8
w
  | Word8
w Word8 -> Word8 -> Bool
forall a. Ord a => a -> a -> Bool
>= Word8
48 Bool -> Bool -> Bool
&& Word8
w Word8 -> Word8 -> Bool
forall a. Ord a => a -> a -> Bool
< Word8
58 = Word -> Maybe Word
forall a. a -> Maybe a
Just (Word8 -> Word
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word8
w Word -> Word -> Word
forall a. Num a => a -> a -> a
- Word
48)
  | Word8
w Word8 -> Word8 -> Bool
forall a. Ord a => a -> a -> Bool
>= Word8
65 Bool -> Bool -> Bool
&& Word8
w Word8 -> Word8 -> Bool
forall a. Ord a => a -> a -> Bool
< Word8
71 = Word -> Maybe Word
forall a. a -> Maybe a
Just (Word8 -> Word
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word8
w Word -> Word -> Word
forall a. Num a => a -> a -> a
- Word
55)
  | Word8
w Word8 -> Word8 -> Bool
forall a. Ord a => a -> a -> Bool
>= Word8
97 Bool -> Bool -> Bool
&& Word8
w Word8 -> Word8 -> Bool
forall a. Ord a => a -> a -> Bool
< Word8
103 = Word -> Maybe Word
forall a. a -> Maybe a
Just (Word8 -> Word
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word8
w Word -> Word -> Word
forall a. Num a => a -> a -> a
- Word
87)
  | Bool
otherwise = Maybe Word
forall a. Maybe a
Nothing

uneffectfulWord# :: (Bytes -> Result# e Word#) -> Parser e s Word#
{-# inline uneffectfulWord# #-}
uneffectfulWord# :: (Bytes -> Result# e Word#) -> Parser e s Word#
uneffectfulWord# Bytes -> Result# e Word#
f = ((# ByteArray#, Int#, Int# #) -> ST# s (Result# e Word#))
-> Parser e s Word#
forall e s a.
((# ByteArray#, Int#, Int# #) -> ST# s (Result# e a))
-> Parser e s a
Parser
  ( \(# ByteArray#, Int#, Int# #)
b State# s
s0 -> (# State# s
s0, (Bytes -> Result# e Word#
f ((# ByteArray#, Int#, Int# #) -> Bytes
boxBytes (# ByteArray#, Int#, Int# #)
b)) #) )

-- Precondition: the arguments are non-negative. Boolean is
-- true when overflow happens. Performs: a * 10 + b
-- Postcondition: when overflow is false, the resulting
-- word is less than or equal to the upper bound
positivePushBase10 :: Word -> Word -> Word -> (Bool,Word)
{-# inline positivePushBase10 #-}
positivePushBase10 :: Word -> Word -> Word -> (Bool, Word)
positivePushBase10 (W# Word#
a) (W# Word#
b) (W# Word#
upper) =
  let !(# Word#
ca, Word#
r0 #) = Word# -> Word# -> (# Word#, Word# #)
Exts.timesWord2# Word#
a Word#
10##
      !r1 :: Word#
r1 = Word# -> Word# -> Word#
Exts.plusWord# Word#
r0 Word#
b
      !cb :: Word#
cb = Int# -> Word#
int2Word# (Word# -> Word# -> Int#
gtWord# Word#
r1 Word#
upper)
      !cc :: Word#
cc = Int# -> Word#
int2Word# (Word# -> Word# -> Int#
ltWord# Word#
r1 Word#
0##)
      !c :: Word#
c = Word#
ca Word# -> Word# -> Word#
`or#` Word#
cb Word# -> Word# -> Word#
`or#` Word#
cc
   in (case Word#
c of { Word#
0## -> Bool
False; Word#
_ -> Bool
True }, Word# -> Word
W# Word#
r1)

unsignedPushBase10 :: Word -> Word -> (Bool,Word)
{-# inline unsignedPushBase10 #-}
unsignedPushBase10 :: Word -> Word -> (Bool, Word)
unsignedPushBase10 (W# Word#
a) (W# Word#
b) =
  let !(# Word#
ca, Word#
r0 #) = Word# -> Word# -> (# Word#, Word# #)
Exts.timesWord2# Word#
a Word#
10##
      !r1 :: Word#
r1 = Word# -> Word# -> Word#
Exts.plusWord# Word#
r0 Word#
b
      !cb :: Word#
cb = Int# -> Word#
int2Word# (Word# -> Word# -> Int#
ltWord# Word#
r1 Word#
r0)
      !c :: Word#
c = Word#
ca Word# -> Word# -> Word#
`or#` Word#
cb
   in (case Word#
c of { Word#
0## -> Bool
False; Word#
_ -> Bool
True }, Word# -> Word
W# Word#
r1)

-- | Skip while the predicate is matched. This is always inlined.
skipWhile :: (Char -> Bool) -> Parser e s ()
{-# inline skipWhile #-}
skipWhile :: (Char -> Bool) -> Parser e s ()
skipWhile Char -> Bool
f = Parser e s ()
forall e s. Parser e s ()
go where
  go :: Parser e s ()
go = Parser e s Bool
forall e s. Parser e s Bool
isEndOfInput Parser e s Bool -> (Bool -> Parser e s ()) -> Parser e s ()
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
    Bool
True -> () -> Parser e s ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure ()
    Bool
False -> do
      Char
w <- Parser e s Char
forall e s. Parser e s Char
anyUnsafe
      if Char -> Bool
f Char
w
        then Parser e s ()
go
        else Int -> Parser e s ()
forall e s. Int -> Parser e s ()
unconsume Int
1

-- Interpret the next byte as an Latin1-encoded character.
-- Does not check to see if any characters are left. This
-- is not exported.
anyUnsafe :: Parser e s Char
{-# inline anyUnsafe #-}
anyUnsafe :: Parser e s Char
anyUnsafe = (Bytes -> Result e Char) -> Parser e s Char
forall e a s. (Bytes -> Result e a) -> Parser e s a
uneffectful ((Bytes -> Result e Char) -> Parser e s Char)
-> (Bytes -> Result e Char) -> Parser e s Char
forall a b. (a -> b) -> a -> b
$ \Bytes
chunk ->
  let w :: Char
w = ByteArray -> Int -> Char
indexCharArray (Bytes -> ByteArray
array Bytes
chunk) (Bytes -> Int
offset Bytes
chunk) :: Char
   in Char -> Int -> Int -> Result e Char
forall e a. a -> Int -> Int -> Result e a
Success Char
w (Bytes -> Int
offset Bytes
chunk Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1) (Bytes -> Int
length Bytes
chunk Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1)

-- Reads one byte and interprets it as Latin1-encoded character.
indexCharArray :: PM.ByteArray -> Int -> Char
{-# inline indexCharArray #-}
indexCharArray :: ByteArray -> Int -> Char
indexCharArray (PM.ByteArray ByteArray#
x) (I# Int#
i) = Char# -> Char
C# (ByteArray# -> Int# -> Char#
indexCharArray# ByteArray#
x Int#
i)

-- | Match any character, to perform lookahead. Returns 'Nothing' if
--   end of input has been reached. Does not consume any input.
--
--   /Note/: Because this parser does not fail, do not use it
--   with combinators such as 'many', because such as 'many',
--   because such parsers loop until a failure occurs. Careless
--   use will thus result in an infinite loop.
peek :: Parser e s (Maybe Char)
{-# inline peek #-}
peek :: Parser e s (Maybe Char)
peek = (Bytes -> Result e (Maybe Char)) -> Parser e s (Maybe Char)
forall e a s. (Bytes -> Result e a) -> Parser e s a
uneffectful ((Bytes -> Result e (Maybe Char)) -> Parser e s (Maybe Char))
-> (Bytes -> Result e (Maybe Char)) -> Parser e s (Maybe Char)
forall a b. (a -> b) -> a -> b
$ \(Bytes ByteArray
arr Int
off Int
len) ->
  let v :: Maybe Char
v = if Int
len Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
0
        then Char -> Maybe Char
forall a. a -> Maybe a
Just (ByteArray -> Int -> Char
indexCharArray ByteArray
arr Int
off)
        else Maybe Char
forall a. Maybe a
Nothing
  in Maybe Char -> Int -> Int -> Result e (Maybe Char)
forall e a. a -> Int -> Int -> Result e a
Success Maybe Char
v Int
off Int
len

-- | Match any byte, to perform lookahead. Does not consume any
--   input, but will fail if end of input has been reached.
peek' :: e -> Parser e s Char
{-# inline peek' #-}
peek' :: e -> Parser e s Char
peek' e
e = (Bytes -> Result e Char) -> Parser e s Char
forall e a s. (Bytes -> Result e a) -> Parser e s a
uneffectful ((Bytes -> Result e Char) -> Parser e s Char)
-> (Bytes -> Result e Char) -> Parser e s Char
forall a b. (a -> b) -> a -> b
$ \(Bytes ByteArray
arr Int
off Int
len) -> if Int
len Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
0
  then Char -> Int -> Int -> Result e Char
forall e a. a -> Int -> Int -> Result e a
Success (ByteArray -> Int -> Char
indexCharArray ByteArray
arr Int
off) Int
off Int
len
  else e -> Result e Char
forall e a. e -> Result e a
Failure e
e