{-# LANGUAGE CPP #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE UnboxedTuples #-}

{- | Provides levity-polymorphic variants of @>>=@, @>>@, and @pure@
used to assemble parsers whose result types are unlifted. This
cannot be used with the @RebindableSyntax@ extension because that
extension disallows representations other than @LiftedRep@. Consequently,
users of this module must manually desugar do notation. See the
@url-bytes@ library for an example of this module in action.

Only resort to the functions in this module after checking that
GHC is unable to optimize away @I#@ and friends in your code.
-}
module Data.Bytes.Parser.Rebindable
  ( Bind (..)
  , Pure (..)
  ) where

import Data.Bytes.Parser.Internal (Parser (..))
import GHC.Exts (RuntimeRep (..), TYPE)
import Prelude ()

#if MIN_VERSION_base(4,16,0)
import GHC.Exts (LiftedRep)
#else
type LiftedRep = 'LiftedRep
#endif

class Bind (ra :: RuntimeRep) (rb :: RuntimeRep) where
  (>>=) ::
    forall e s (a :: TYPE ra) (b :: TYPE rb).
    Parser e s a ->
    (a -> Parser e s b) ->
    Parser e s b
  (>>) ::
    forall e s (a :: TYPE ra) (b :: TYPE rb).
    Parser e s a ->
    Parser e s b ->
    Parser e s b

class Pure (ra :: RuntimeRep) where
  pure :: forall e s (a :: TYPE ra). a -> Parser e s a

pureParser :: a -> Parser e s a
{-# INLINE pureParser #-}
pureParser :: forall a e s. a -> Parser e s a
pureParser a
a =
  ((# ByteArray#, Int#, Int# #) -> ST# s (Result# e a))
-> Parser e s a
forall a b c.
((# ByteArray#, Int#, Int# #) -> ST# b (Result# a c))
-> Parser a b c
Parser
    (\(# ByteArray#
_, Int#
b, Int#
c #) State# s
s -> (# State# s
s, (# | (# a
a, Int#
b, Int#
c #) #) #))

bindParser :: Parser e s a -> (a -> Parser e s b) -> Parser e s b
{-# INLINE bindParser #-}
bindParser :: forall e s a b. Parser e s a -> (a -> Parser e s b) -> Parser e s b
bindParser (Parser (# ByteArray#, Int#, Int# #) -> ST# s (Result# e a)
f) a -> Parser e s b
g =
  ((# ByteArray#, Int#, Int# #) -> ST# s (Result# e b))
-> Parser e s b
forall a b c.
((# ByteArray#, Int#, Int# #) -> ST# b (Result# a c))
-> Parser a b c
Parser
    ( \x :: (# ByteArray#, Int#, Int# #)
x@(# ByteArray#
arr, Int#
_, Int#
_ #) State# s
s0 -> case (# ByteArray#, Int#, Int# #) -> ST# s (Result# e a)
f (# ByteArray#, Int#, Int# #)
x State# s
s0 of
        (# State# s
s1, Result# e a
r0 #) -> case Result# e a
r0 of
          (# e
e | #) -> (# State# s
s1, (# e
e | #) #)
          (# | (# a
y, Int#
b, Int#
c #) #) ->
            Parser e s b -> (# ByteArray#, Int#, Int# #) -> ST# s (Result# e b)
forall e s a.
Parser e s a -> (# ByteArray#, Int#, Int# #) -> ST# s (Result# e a)
runParser (a -> Parser e s b
g a
y) (# ByteArray#
arr, Int#
b, Int#
c #) State# s
s1
    )

sequenceParser :: Parser e s a -> Parser e s b -> Parser e s b
{-# INLINE sequenceParser #-}
sequenceParser :: forall e s a b. Parser e s a -> Parser e s b -> Parser e s b
sequenceParser (Parser (# ByteArray#, Int#, Int# #) -> ST# s (Result# e a)
f) (Parser (# ByteArray#, Int#, Int# #) -> ST# s (Result# e b)
g) =
  ((# ByteArray#, Int#, Int# #) -> ST# s (Result# e b))
-> Parser e s b
forall a b c.
((# ByteArray#, Int#, Int# #) -> ST# b (Result# a c))
-> Parser a b c
Parser
    ( \x :: (# ByteArray#, Int#, Int# #)
x@(# ByteArray#
arr, Int#
_, Int#
_ #) State# s
s0 -> case (# ByteArray#, Int#, Int# #) -> ST# s (Result# e a)
f (# ByteArray#, Int#, Int# #)
x State# s
s0 of
        (# State# s
s1, Result# e a
r0 #) -> case Result# e a
r0 of
          (# e
e | #) -> (# State# s
s1, (# e
e | #) #)
          (# | (# a
_, Int#
b, Int#
c #) #) -> (# ByteArray#, Int#, Int# #) -> ST# s (Result# e b)
g (# ByteArray#
arr, Int#
b, Int#
c #) State# s
s1
    )

pureIntParser ::
  forall (a :: TYPE 'IntRep) e s.
  a ->
  Parser e s a
{-# INLINE pureIntParser #-}
pureIntParser :: forall (a :: TYPE 'IntRep) e s. a -> Parser e s a
pureIntParser a
a =
  ((# ByteArray#, Int#, Int# #) -> ST# s (Result# e a))
-> Parser e s a
forall a b c.
((# ByteArray#, Int#, Int# #) -> ST# b (Result# a c))
-> Parser a b c
Parser
    (\(# ByteArray#
_, Int#
b, Int#
c #) State# s
s -> (# State# s
s, (# | (# a
a, Int#
b, Int#
c #) #) #))

bindIntParser ::
  forall (a :: TYPE 'IntRep) e s b.
  Parser e s a ->
  (a -> Parser e s b) ->
  Parser e s b
{-# INLINE bindIntParser #-}
bindIntParser :: forall (a :: TYPE 'IntRep) e s b.
Parser e s a -> (a -> Parser e s b) -> Parser e s b
bindIntParser (Parser (# ByteArray#, Int#, Int# #) -> ST# s (Result# e a)
f) a -> Parser e s b
g =
  ((# ByteArray#, Int#, Int# #) -> ST# s (Result# e b))
-> Parser e s b
forall a b c.
((# ByteArray#, Int#, Int# #) -> ST# b (Result# a c))
-> Parser a b c
Parser
    ( \x :: (# ByteArray#, Int#, Int# #)
x@(# ByteArray#
arr, Int#
_, Int#
_ #) State# s
s0 -> case (# ByteArray#, Int#, Int# #) -> ST# s (Result# e a)
f (# ByteArray#, Int#, Int# #)
x State# s
s0 of
        (# State# s
s1, Result# e a
r0 #) -> case Result# e a
r0 of
          (# e
e | #) -> (# State# s
s1, (# e
e | #) #)
          (# | (# a
y, Int#
b, Int#
c #) #) ->
            Parser e s b -> (# ByteArray#, Int#, Int# #) -> ST# s (Result# e b)
forall e s a.
Parser e s a -> (# ByteArray#, Int#, Int# #) -> ST# s (Result# e a)
runParser (a -> Parser e s b
g a
y) (# ByteArray#
arr, Int#
b, Int#
c #) State# s
s1
    )

bindWordParser ::
  forall (a :: TYPE 'WordRep) e s b.
  Parser e s a ->
  (a -> Parser e s b) ->
  Parser e s b
{-# INLINE bindWordParser #-}
bindWordParser :: forall (a :: TYPE 'WordRep) e s b.
Parser e s a -> (a -> Parser e s b) -> Parser e s b
bindWordParser (Parser (# ByteArray#, Int#, Int# #) -> ST# s (Result# e a)
f) a -> Parser e s b
g =
  ((# ByteArray#, Int#, Int# #) -> ST# s (Result# e b))
-> Parser e s b
forall a b c.
((# ByteArray#, Int#, Int# #) -> ST# b (Result# a c))
-> Parser a b c
Parser
    ( \x :: (# ByteArray#, Int#, Int# #)
x@(# ByteArray#
arr, Int#
_, Int#
_ #) State# s
s0 -> case (# ByteArray#, Int#, Int# #) -> ST# s (Result# e a)
f (# ByteArray#, Int#, Int# #)
x State# s
s0 of
        (# State# s
s1, Result# e a
r0 #) -> case Result# e a
r0 of
          (# e
e | #) -> (# State# s
s1, (# e
e | #) #)
          (# | (# a
y, Int#
b, Int#
c #) #) ->
            Parser e s b -> (# ByteArray#, Int#, Int# #) -> ST# s (Result# e b)
forall e s a.
Parser e s a -> (# ByteArray#, Int#, Int# #) -> ST# s (Result# e a)
runParser (a -> Parser e s b
g a
y) (# ByteArray#
arr, Int#
b, Int#
c #) State# s
s1
    )

sequenceIntParser ::
  forall (a :: TYPE 'IntRep) e s b.
  Parser e s a ->
  Parser e s b ->
  Parser e s b
{-# INLINE sequenceIntParser #-}
sequenceIntParser :: forall (a :: TYPE 'IntRep) e s b.
Parser e s a -> Parser e s b -> Parser e s b
sequenceIntParser (Parser (# ByteArray#, Int#, Int# #) -> ST# s (Result# e a)
f) (Parser (# ByteArray#, Int#, Int# #) -> ST# s (Result# e b)
g) =
  ((# ByteArray#, Int#, Int# #) -> ST# s (Result# e b))
-> Parser e s b
forall a b c.
((# ByteArray#, Int#, Int# #) -> ST# b (Result# a c))
-> Parser a b c
Parser
    ( \x :: (# ByteArray#, Int#, Int# #)
x@(# ByteArray#
arr, Int#
_, Int#
_ #) State# s
s0 -> case (# ByteArray#, Int#, Int# #) -> ST# s (Result# e a)
f (# ByteArray#, Int#, Int# #)
x State# s
s0 of
        (# State# s
s1, Result# e a
r0 #) -> case Result# e a
r0 of
          (# e
e | #) -> (# State# s
s1, (# e
e | #) #)
          (# | (# a
_, Int#
b, Int#
c #) #) -> (# ByteArray#, Int#, Int# #) -> ST# s (Result# e b)
g (# ByteArray#
arr, Int#
b, Int#
c #) State# s
s1
    )

sequenceWordParser ::
  forall (a :: TYPE 'WordRep) e s b.
  Parser e s a ->
  Parser e s b ->
  Parser e s b
{-# INLINE sequenceWordParser #-}
sequenceWordParser :: forall (a :: TYPE 'WordRep) e s b.
Parser e s a -> Parser e s b -> Parser e s b
sequenceWordParser (Parser (# ByteArray#, Int#, Int# #) -> ST# s (Result# e a)
f) (Parser (# ByteArray#, Int#, Int# #) -> ST# s (Result# e b)
g) =
  ((# ByteArray#, Int#, Int# #) -> ST# s (Result# e b))
-> Parser e s b
forall a b c.
((# ByteArray#, Int#, Int# #) -> ST# b (Result# a c))
-> Parser a b c
Parser
    ( \x :: (# ByteArray#, Int#, Int# #)
x@(# ByteArray#
arr, Int#
_, Int#
_ #) State# s
s0 -> case (# ByteArray#, Int#, Int# #) -> ST# s (Result# e a)
f (# ByteArray#, Int#, Int# #)
x State# s
s0 of
        (# State# s
s1, Result# e a
r0 #) -> case Result# e a
r0 of
          (# e
e | #) -> (# State# s
s1, (# e
e | #) #)
          (# | (# a
_, Int#
b, Int#
c #) #) -> (# ByteArray#, Int#, Int# #) -> ST# s (Result# e b)
g (# ByteArray#
arr, Int#
b, Int#
c #) State# s
s1
    )

pureIntPairParser ::
  forall (a :: TYPE ('TupleRep '[ 'IntRep, 'IntRep])) e s.
  a ->
  Parser e s a
{-# INLINE pureIntPairParser #-}
pureIntPairParser :: forall (a :: TYPE ('TupleRep '[ 'IntRep, 'IntRep])) e s.
a -> Parser e s a
pureIntPairParser a
a =
  ((# ByteArray#, Int#, Int# #) -> ST# s (Result# e a))
-> Parser e s a
forall a b c.
((# ByteArray#, Int#, Int# #) -> ST# b (Result# a c))
-> Parser a b c
Parser
    (\(# ByteArray#
_, Int#
b, Int#
c #) State# s
s -> (# State# s
s, (# | (# a
a, Int#
b, Int#
c #) #) #))

bindIntPairParser ::
  forall (a :: TYPE ('TupleRep '[ 'IntRep, 'IntRep])) e s b.
  Parser e s a ->
  (a -> Parser e s b) ->
  Parser e s b
{-# INLINE bindIntPairParser #-}
bindIntPairParser :: forall (a :: TYPE ('TupleRep '[ 'IntRep, 'IntRep])) e s b.
Parser e s a -> (a -> Parser e s b) -> Parser e s b
bindIntPairParser (Parser (# ByteArray#, Int#, Int# #) -> ST# s (Result# e a)
f) a -> Parser e s b
g =
  ((# ByteArray#, Int#, Int# #) -> ST# s (Result# e b))
-> Parser e s b
forall a b c.
((# ByteArray#, Int#, Int# #) -> ST# b (Result# a c))
-> Parser a b c
Parser
    ( \x :: (# ByteArray#, Int#, Int# #)
x@(# ByteArray#
arr, Int#
_, Int#
_ #) State# s
s0 -> case (# ByteArray#, Int#, Int# #) -> ST# s (Result# e a)
f (# ByteArray#, Int#, Int# #)
x State# s
s0 of
        (# State# s
s1, Result# e a
r0 #) -> case Result# e a
r0 of
          (# e
e | #) -> (# State# s
s1, (# e
e | #) #)
          (# | (# a
y, Int#
b, Int#
c #) #) ->
            Parser e s b -> (# ByteArray#, Int#, Int# #) -> ST# s (Result# e b)
forall e s a.
Parser e s a -> (# ByteArray#, Int#, Int# #) -> ST# s (Result# e a)
runParser (a -> Parser e s b
g a
y) (# ByteArray#
arr, Int#
b, Int#
c #) State# s
s1
    )

pureInt5Parser ::
  forall (a :: TYPE ('TupleRep '[ 'IntRep, 'IntRep, 'IntRep, 'IntRep, 'IntRep])) e s.
  a ->
  Parser e s a
{-# INLINE pureInt5Parser #-}
pureInt5Parser :: forall (a :: TYPE
               ('TupleRep '[ 'IntRep, 'IntRep, 'IntRep, 'IntRep, 'IntRep]))
       e s.
a -> Parser e s a
pureInt5Parser a
a =
  ((# ByteArray#, Int#, Int# #) -> ST# s (Result# e a))
-> Parser e s a
forall a b c.
((# ByteArray#, Int#, Int# #) -> ST# b (Result# a c))
-> Parser a b c
Parser
    (\(# ByteArray#
_, Int#
b, Int#
c #) State# s
s -> (# State# s
s, (# | (# a
a, Int#
b, Int#
c #) #) #))

bindInt5Parser ::
  forall (a :: TYPE ('TupleRep '[ 'IntRep, 'IntRep, 'IntRep, 'IntRep, 'IntRep])) e s b.
  Parser e s a ->
  (a -> Parser e s b) ->
  Parser e s b
{-# INLINE bindInt5Parser #-}
bindInt5Parser :: forall (a :: TYPE
               ('TupleRep '[ 'IntRep, 'IntRep, 'IntRep, 'IntRep, 'IntRep]))
       e s b.
Parser e s a -> (a -> Parser e s b) -> Parser e s b
bindInt5Parser (Parser (# ByteArray#, Int#, Int# #) -> ST# s (Result# e a)
f) a -> Parser e s b
g =
  ((# ByteArray#, Int#, Int# #) -> ST# s (Result# e b))
-> Parser e s b
forall a b c.
((# ByteArray#, Int#, Int# #) -> ST# b (Result# a c))
-> Parser a b c
Parser
    ( \x :: (# ByteArray#, Int#, Int# #)
x@(# ByteArray#
arr, Int#
_, Int#
_ #) State# s
s0 -> case (# ByteArray#, Int#, Int# #) -> ST# s (Result# e a)
f (# ByteArray#, Int#, Int# #)
x State# s
s0 of
        (# State# s
s1, Result# e a
r0 #) -> case Result# e a
r0 of
          (# e
e | #) -> (# State# s
s1, (# e
e | #) #)
          (# | (# a
y, Int#
b, Int#
c #) #) ->
            Parser e s b -> (# ByteArray#, Int#, Int# #) -> ST# s (Result# e b)
forall e s a.
Parser e s a -> (# ByteArray#, Int#, Int# #) -> ST# s (Result# e a)
runParser (a -> Parser e s b
g a
y) (# ByteArray#
arr, Int#
b, Int#
c #) State# s
s1
    )

sequenceInt5Parser ::
  forall (a :: TYPE ('TupleRep '[ 'IntRep, 'IntRep, 'IntRep, 'IntRep, 'IntRep])) e s b.
  Parser e s a ->
  Parser e s b ->
  Parser e s b
{-# INLINE sequenceInt5Parser #-}
sequenceInt5Parser :: forall (a :: TYPE
               ('TupleRep '[ 'IntRep, 'IntRep, 'IntRep, 'IntRep, 'IntRep]))
       e s b.
Parser e s a -> Parser e s b -> Parser e s b
sequenceInt5Parser (Parser (# ByteArray#, Int#, Int# #) -> ST# s (Result# e a)
f) (Parser (# ByteArray#, Int#, Int# #) -> ST# s (Result# e b)
g) =
  ((# ByteArray#, Int#, Int# #) -> ST# s (Result# e b))
-> Parser e s b
forall a b c.
((# ByteArray#, Int#, Int# #) -> ST# b (Result# a c))
-> Parser a b c
Parser
    ( \x :: (# ByteArray#, Int#, Int# #)
x@(# ByteArray#
arr, Int#
_, Int#
_ #) State# s
s0 -> case (# ByteArray#, Int#, Int# #) -> ST# s (Result# e a)
f (# ByteArray#, Int#, Int# #)
x State# s
s0 of
        (# State# s
s1, Result# e a
r0 #) -> case Result# e a
r0 of
          (# e
e | #) -> (# State# s
s1, (# e
e | #) #)
          (# | (# a
_, Int#
b, Int#
c #) #) -> (# ByteArray#, Int#, Int# #) -> ST# s (Result# e b)
g (# ByteArray#
arr, Int#
b, Int#
c #) State# s
s1
    )

sequenceIntPairParser ::
  forall (a :: TYPE ('TupleRep '[ 'IntRep, 'IntRep])) e s b.
  Parser e s a ->
  Parser e s b ->
  Parser e s b
{-# INLINE sequenceIntPairParser #-}
sequenceIntPairParser :: forall (a :: TYPE ('TupleRep '[ 'IntRep, 'IntRep])) e s b.
Parser e s a -> Parser e s b -> Parser e s b
sequenceIntPairParser (Parser (# ByteArray#, Int#, Int# #) -> ST# s (Result# e a)
f) (Parser (# ByteArray#, Int#, Int# #) -> ST# s (Result# e b)
g) =
  ((# ByteArray#, Int#, Int# #) -> ST# s (Result# e b))
-> Parser e s b
forall a b c.
((# ByteArray#, Int#, Int# #) -> ST# b (Result# a c))
-> Parser a b c
Parser
    ( \x :: (# ByteArray#, Int#, Int# #)
x@(# ByteArray#
arr, Int#
_, Int#
_ #) State# s
s0 -> case (# ByteArray#, Int#, Int# #) -> ST# s (Result# e a)
f (# ByteArray#, Int#, Int# #)
x State# s
s0 of
        (# State# s
s1, Result# e a
r0 #) -> case Result# e a
r0 of
          (# e
e | #) -> (# State# s
s1, (# e
e | #) #)
          (# | (# a
_, Int#
b, Int#
c #) #) -> (# ByteArray#, Int#, Int# #) -> ST# s (Result# e b)
g (# ByteArray#
arr, Int#
b, Int#
c #) State# s
s1
    )

bindInt2to5Parser ::
  forall
    (a :: TYPE ('TupleRep '[ 'IntRep, 'IntRep]))
    (b :: TYPE ('TupleRep '[ 'IntRep, 'IntRep, 'IntRep, 'IntRep, 'IntRep]))
    e
    s.
  Parser e s a ->
  (a -> Parser e s b) ->
  Parser e s b
{-# INLINE bindInt2to5Parser #-}
bindInt2to5Parser :: forall (a :: TYPE ('TupleRep '[ 'IntRep, 'IntRep]))
       (b :: TYPE
               ('TupleRep '[ 'IntRep, 'IntRep, 'IntRep, 'IntRep, 'IntRep]))
       e s.
Parser e s a -> (a -> Parser e s b) -> Parser e s b
bindInt2to5Parser (Parser (# ByteArray#, Int#, Int# #) -> ST# s (Result# e a)
f) a -> Parser e s b
g =
  ((# ByteArray#, Int#, Int# #) -> ST# s (Result# e b))
-> Parser e s b
forall a b c.
((# ByteArray#, Int#, Int# #) -> ST# b (Result# a c))
-> Parser a b c
Parser
    ( \x :: (# ByteArray#, Int#, Int# #)
x@(# ByteArray#
arr, Int#
_, Int#
_ #) State# s
s0 -> case (# ByteArray#, Int#, Int# #) -> ST# s (Result# e a)
f (# ByteArray#, Int#, Int# #)
x State# s
s0 of
        (# State# s
s1, Result# e a
r0 #) -> case Result# e a
r0 of
          (# e
e | #) -> (# State# s
s1, (# e
e | #) #)
          (# | (# a
y, Int#
b, Int#
c #) #) ->
            Parser e s b -> (# ByteArray#, Int#, Int# #) -> ST# s (Result# e b)
forall e s a.
Parser e s a -> (# ByteArray#, Int#, Int# #) -> ST# s (Result# e a)
runParser (a -> Parser e s b
g a
y) (# ByteArray#
arr, Int#
b, Int#
c #) State# s
s1
    )

sequenceInt2to5Parser ::
  forall
    (a :: TYPE ('TupleRep '[ 'IntRep, 'IntRep]))
    (b :: TYPE ('TupleRep '[ 'IntRep, 'IntRep, 'IntRep, 'IntRep, 'IntRep]))
    e
    s.
  Parser e s a ->
  Parser e s b ->
  Parser e s b
{-# INLINE sequenceInt2to5Parser #-}
sequenceInt2to5Parser :: forall (a :: TYPE ('TupleRep '[ 'IntRep, 'IntRep]))
       (b :: TYPE
               ('TupleRep '[ 'IntRep, 'IntRep, 'IntRep, 'IntRep, 'IntRep]))
       e s.
Parser e s a -> Parser e s b -> Parser e s b
sequenceInt2to5Parser (Parser (# ByteArray#, Int#, Int# #) -> ST# s (Result# e a)
f) (Parser (# ByteArray#, Int#, Int# #) -> ST# s (Result# e b)
g) =
  ((# ByteArray#, Int#, Int# #) -> ST# s (Result# e b))
-> Parser e s b
forall a b c.
((# ByteArray#, Int#, Int# #) -> ST# b (Result# a c))
-> Parser a b c
Parser
    ( \x :: (# ByteArray#, Int#, Int# #)
x@(# ByteArray#
arr, Int#
_, Int#
_ #) State# s
s0 -> case (# ByteArray#, Int#, Int# #) -> ST# s (Result# e a)
f (# ByteArray#, Int#, Int# #)
x State# s
s0 of
        (# State# s
s1, Result# e a
r0 #) -> case Result# e a
r0 of
          (# e
e | #) -> (# State# s
s1, (# e
e | #) #)
          (# | (# a
_, Int#
b, Int#
c #) #) -> (# ByteArray#, Int#, Int# #) -> ST# s (Result# e b)
g (# ByteArray#
arr, Int#
b, Int#
c #) State# s
s1
    )

instance Bind LiftedRep LiftedRep where
  {-# INLINE (>>=) #-}
  {-# INLINE (>>) #-}
  >>= :: forall e s a b. Parser e s a -> (a -> Parser e s b) -> Parser e s b
(>>=) = Parser e s a -> (a -> Parser e s b) -> Parser e s b
forall e s a b. Parser e s a -> (a -> Parser e s b) -> Parser e s b
bindParser
  >> :: forall e s a b. Parser e s a -> Parser e s b -> Parser e s b
(>>) = Parser e s a -> Parser e s b -> Parser e s b
forall e s a b. Parser e s a -> Parser e s b -> Parser e s b
sequenceParser

instance Bind 'WordRep LiftedRep where
  {-# INLINE (>>=) #-}
  {-# INLINE (>>) #-}
  >>= :: forall e s (a :: TYPE 'WordRep) b.
Parser e s a -> (a -> Parser e s b) -> Parser e s b
(>>=) = Parser e s a -> (a -> Parser e s b) -> Parser e s b
forall (a :: TYPE 'WordRep) e s b.
Parser e s a -> (a -> Parser e s b) -> Parser e s b
bindWordParser
  >> :: forall e s (a :: TYPE 'WordRep) b.
Parser e s a -> Parser e s b -> Parser e s b
(>>) = Parser e s a -> Parser e s b -> Parser e s b
forall (a :: TYPE 'WordRep) e s b.
Parser e s a -> Parser e s b -> Parser e s b
sequenceWordParser

instance Bind 'IntRep LiftedRep where
  {-# INLINE (>>=) #-}
  {-# INLINE (>>) #-}
  >>= :: forall e s (a :: TYPE 'IntRep) b.
Parser e s a -> (a -> Parser e s b) -> Parser e s b
(>>=) = Parser e s a -> (a -> Parser e s b) -> Parser e s b
forall (a :: TYPE 'IntRep) e s b.
Parser e s a -> (a -> Parser e s b) -> Parser e s b
bindIntParser
  >> :: forall e s (a :: TYPE 'IntRep) b.
Parser e s a -> Parser e s b -> Parser e s b
(>>) = Parser e s a -> Parser e s b -> Parser e s b
forall (a :: TYPE 'IntRep) e s b.
Parser e s a -> Parser e s b -> Parser e s b
sequenceIntParser

instance Bind ('TupleRep '[ 'IntRep, 'IntRep]) LiftedRep where
  {-# INLINE (>>=) #-}
  {-# INLINE (>>) #-}
  >>= :: forall e s (a :: TYPE ('TupleRep '[ 'IntRep, 'IntRep])) b.
Parser e s a -> (a -> Parser e s b) -> Parser e s b
(>>=) = Parser e s a -> (a -> Parser e s b) -> Parser e s b
forall (a :: TYPE ('TupleRep '[ 'IntRep, 'IntRep])) e s b.
Parser e s a -> (a -> Parser e s b) -> Parser e s b
bindIntPairParser
  >> :: forall e s (a :: TYPE ('TupleRep '[ 'IntRep, 'IntRep])) b.
Parser e s a -> Parser e s b -> Parser e s b
(>>) = Parser e s a -> Parser e s b -> Parser e s b
forall (a :: TYPE ('TupleRep '[ 'IntRep, 'IntRep])) e s b.
Parser e s a -> Parser e s b -> Parser e s b
sequenceIntPairParser

instance
  Bind
    ('TupleRep '[ 'IntRep, 'IntRep])
    ('TupleRep '[ 'IntRep, 'IntRep, 'IntRep, 'IntRep, 'IntRep])
  where
  {-# INLINE (>>=) #-}
  {-# INLINE (>>) #-}
  >>= :: forall e s (a :: TYPE ('TupleRep '[ 'IntRep, 'IntRep]))
       (b :: TYPE
               ('TupleRep '[ 'IntRep, 'IntRep, 'IntRep, 'IntRep, 'IntRep])).
Parser e s a -> (a -> Parser e s b) -> Parser e s b
(>>=) = Parser e s a -> (a -> Parser e s b) -> Parser e s b
forall (a :: TYPE ('TupleRep '[ 'IntRep, 'IntRep]))
       (b :: TYPE
               ('TupleRep '[ 'IntRep, 'IntRep, 'IntRep, 'IntRep, 'IntRep]))
       e s.
Parser e s a -> (a -> Parser e s b) -> Parser e s b
bindInt2to5Parser
  >> :: forall e s (a :: TYPE ('TupleRep '[ 'IntRep, 'IntRep]))
       (b :: TYPE
               ('TupleRep '[ 'IntRep, 'IntRep, 'IntRep, 'IntRep, 'IntRep])).
Parser e s a -> Parser e s b -> Parser e s b
(>>) = Parser e s a -> Parser e s b -> Parser e s b
forall (a :: TYPE ('TupleRep '[ 'IntRep, 'IntRep]))
       (b :: TYPE
               ('TupleRep '[ 'IntRep, 'IntRep, 'IntRep, 'IntRep, 'IntRep]))
       e s.
Parser e s a -> Parser e s b -> Parser e s b
sequenceInt2to5Parser

instance
  Bind
    ('TupleRep '[ 'IntRep, 'IntRep, 'IntRep, 'IntRep, 'IntRep])
    LiftedRep
  where
  {-# INLINE (>>=) #-}
  {-# INLINE (>>) #-}
  >>= :: forall e s
       (a :: TYPE
               ('TupleRep '[ 'IntRep, 'IntRep, 'IntRep, 'IntRep, 'IntRep]))
       b.
Parser e s a -> (a -> Parser e s b) -> Parser e s b
(>>=) = Parser e s a -> (a -> Parser e s b) -> Parser e s b
forall (a :: TYPE
               ('TupleRep '[ 'IntRep, 'IntRep, 'IntRep, 'IntRep, 'IntRep]))
       e s b.
Parser e s a -> (a -> Parser e s b) -> Parser e s b
bindInt5Parser
  >> :: forall e s
       (a :: TYPE
               ('TupleRep '[ 'IntRep, 'IntRep, 'IntRep, 'IntRep, 'IntRep]))
       b.
Parser e s a -> Parser e s b -> Parser e s b
(>>) = Parser e s a -> Parser e s b -> Parser e s b
forall (a :: TYPE
               ('TupleRep '[ 'IntRep, 'IntRep, 'IntRep, 'IntRep, 'IntRep]))
       e s b.
Parser e s a -> Parser e s b -> Parser e s b
sequenceInt5Parser

instance
  Bind
    'IntRep
    ('TupleRep '[ 'IntRep, 'IntRep, 'IntRep, 'IntRep, 'IntRep])
  where
  {-# INLINE (>>=) #-}
  {-# INLINE (>>) #-}
  >>= :: forall e s (a :: TYPE 'IntRep)
       (b :: TYPE
               ('TupleRep '[ 'IntRep, 'IntRep, 'IntRep, 'IntRep, 'IntRep])).
Parser e s a -> (a -> Parser e s b) -> Parser e s b
(>>=) = Parser e s a -> (a -> Parser e s b) -> Parser e s b
forall e s (a :: TYPE 'IntRep)
       (b :: TYPE
               ('TupleRep '[ 'IntRep, 'IntRep, 'IntRep, 'IntRep, 'IntRep])).
Parser e s a -> (a -> Parser e s b) -> Parser e s b
bindFromIntToInt5
  >> :: forall e s (a :: TYPE 'IntRep)
       (b :: TYPE
               ('TupleRep '[ 'IntRep, 'IntRep, 'IntRep, 'IntRep, 'IntRep])).
Parser e s a -> Parser e s b -> Parser e s b
(>>) = Parser e s a -> Parser e s b -> Parser e s b
forall e s (a :: TYPE 'IntRep)
       (b :: TYPE
               ('TupleRep '[ 'IntRep, 'IntRep, 'IntRep, 'IntRep, 'IntRep])).
Parser e s a -> Parser e s b -> Parser e s b
sequenceIntToInt5

instance Bind LiftedRep ('TupleRep '[ 'IntRep, 'IntRep]) where
  {-# INLINE (>>=) #-}
  {-# INLINE (>>) #-}
  >>= :: forall e s a (b :: TYPE ('TupleRep '[ 'IntRep, 'IntRep])).
Parser e s a -> (a -> Parser e s b) -> Parser e s b
(>>=) = Parser e s a -> (a -> Parser e s b) -> Parser e s b
forall e s a (b :: TYPE ('TupleRep '[ 'IntRep, 'IntRep])).
Parser e s a -> (a -> Parser e s b) -> Parser e s b
bindFromLiftedToIntPair
  >> :: forall e s a (b :: TYPE ('TupleRep '[ 'IntRep, 'IntRep])).
Parser e s a -> Parser e s b -> Parser e s b
(>>) = Parser e s a -> Parser e s b -> Parser e s b
forall e s a (b :: TYPE ('TupleRep '[ 'IntRep, 'IntRep])).
Parser e s a -> Parser e s b -> Parser e s b
sequenceLiftedToIntPair

instance
  Bind
    LiftedRep
    ('TupleRep '[ 'IntRep, 'IntRep, 'IntRep, 'IntRep, 'IntRep])
  where
  {-# INLINE (>>=) #-}
  {-# INLINE (>>) #-}
  >>= :: forall e s a
       (b :: TYPE
               ('TupleRep '[ 'IntRep, 'IntRep, 'IntRep, 'IntRep, 'IntRep])).
Parser e s a -> (a -> Parser e s b) -> Parser e s b
(>>=) = Parser e s a -> (a -> Parser e s b) -> Parser e s b
forall e s a
       (b :: TYPE
               ('TupleRep '[ 'IntRep, 'IntRep, 'IntRep, 'IntRep, 'IntRep])).
Parser e s a -> (a -> Parser e s b) -> Parser e s b
bindFromLiftedToInt5
  >> :: forall e s a
       (b :: TYPE
               ('TupleRep '[ 'IntRep, 'IntRep, 'IntRep, 'IntRep, 'IntRep])).
Parser e s a -> Parser e s b -> Parser e s b
(>>) = Parser e s a -> Parser e s b -> Parser e s b
forall e s a
       (b :: TYPE
               ('TupleRep '[ 'IntRep, 'IntRep, 'IntRep, 'IntRep, 'IntRep])).
Parser e s a -> Parser e s b -> Parser e s b
sequenceLiftedToInt5

instance Bind 'IntRep ('TupleRep '[ 'IntRep, 'IntRep]) where
  {-# INLINE (>>=) #-}
  {-# INLINE (>>) #-}
  >>= :: forall e s (a :: TYPE 'IntRep)
       (b :: TYPE ('TupleRep '[ 'IntRep, 'IntRep])).
Parser e s a -> (a -> Parser e s b) -> Parser e s b
(>>=) = Parser e s a -> (a -> Parser e s b) -> Parser e s b
forall e s (a :: TYPE 'IntRep)
       (b :: TYPE ('TupleRep '[ 'IntRep, 'IntRep])).
Parser e s a -> (a -> Parser e s b) -> Parser e s b
bindFromIntToIntPair
  >> :: forall e s (a :: TYPE 'IntRep)
       (b :: TYPE ('TupleRep '[ 'IntRep, 'IntRep])).
Parser e s a -> Parser e s b -> Parser e s b
(>>) = Parser e s a -> Parser e s b -> Parser e s b
forall e s (a :: TYPE 'IntRep)
       (b :: TYPE ('TupleRep '[ 'IntRep, 'IntRep])).
Parser e s a -> Parser e s b -> Parser e s b
sequenceIntToIntPair

instance Bind LiftedRep 'IntRep where
  {-# INLINE (>>=) #-}
  {-# INLINE (>>) #-}
  >>= :: forall e s a (b :: TYPE 'IntRep).
Parser e s a -> (a -> Parser e s b) -> Parser e s b
(>>=) = Parser e s a -> (a -> Parser e s b) -> Parser e s b
forall e s a (b :: TYPE 'IntRep).
Parser e s a -> (a -> Parser e s b) -> Parser e s b
bindFromLiftedToInt
  >> :: forall e s a (b :: TYPE 'IntRep).
Parser e s a -> Parser e s b -> Parser e s b
(>>) = Parser e s a -> Parser e s b -> Parser e s b
forall e s a (b :: TYPE 'IntRep).
Parser e s a -> Parser e s b -> Parser e s b
sequenceLiftedToInt

instance Pure LiftedRep where
  {-# INLINE pure #-}
  pure :: forall e s a. a -> Parser e s a
pure = a -> Parser e s a
forall a e s. a -> Parser e s a
pureParser

instance Pure 'IntRep where
  {-# INLINE pure #-}
  pure :: forall e s (a :: TYPE 'IntRep). a -> Parser e s a
pure = a -> Parser e s a
forall (a :: TYPE 'IntRep) e s. a -> Parser e s a
pureIntParser

instance Pure ('TupleRep '[ 'IntRep, 'IntRep]) where
  {-# INLINE pure #-}
  pure :: forall e s (a :: TYPE ('TupleRep '[ 'IntRep, 'IntRep])).
a -> Parser e s a
pure = a -> Parser e s a
forall (a :: TYPE ('TupleRep '[ 'IntRep, 'IntRep])) e s.
a -> Parser e s a
pureIntPairParser

instance Pure ('TupleRep '[ 'IntRep, 'IntRep, 'IntRep, 'IntRep, 'IntRep]) where
  {-# INLINE pure #-}
  pure :: forall e s
       (a :: TYPE
               ('TupleRep '[ 'IntRep, 'IntRep, 'IntRep, 'IntRep, 'IntRep])).
a -> Parser e s a
pure = a -> Parser e s a
forall (a :: TYPE
               ('TupleRep '[ 'IntRep, 'IntRep, 'IntRep, 'IntRep, 'IntRep]))
       e s.
a -> Parser e s a
pureInt5Parser

bindFromIntToIntPair ::
  forall
    s
    e
    (a :: TYPE 'IntRep)
    (b :: TYPE ('TupleRep '[ 'IntRep, 'IntRep])).
  Parser s e a ->
  (a -> Parser s e b) ->
  Parser s e b
{-# INLINE bindFromIntToIntPair #-}
bindFromIntToIntPair :: forall e s (a :: TYPE 'IntRep)
       (b :: TYPE ('TupleRep '[ 'IntRep, 'IntRep])).
Parser e s a -> (a -> Parser e s b) -> Parser e s b
bindFromIntToIntPair (Parser (# ByteArray#, Int#, Int# #) -> ST# e (Result# s a)
f) a -> Parser s e b
g =
  ((# ByteArray#, Int#, Int# #) -> ST# e (Result# s b))
-> Parser s e b
forall a b c.
((# ByteArray#, Int#, Int# #) -> ST# b (Result# a c))
-> Parser a b c
Parser
    ( \x :: (# ByteArray#, Int#, Int# #)
x@(# ByteArray#
arr, Int#
_, Int#
_ #) State# e
s0 -> case (# ByteArray#, Int#, Int# #) -> ST# e (Result# s a)
f (# ByteArray#, Int#, Int# #)
x State# e
s0 of
        (# State# e
s1, Result# s a
r0 #) -> case Result# s a
r0 of
          (# s
e | #) -> (# State# e
s1, (# s
e | #) #)
          (# | (# a
y, Int#
b, Int#
c #) #) ->
            Parser s e b -> (# ByteArray#, Int#, Int# #) -> ST# e (Result# s b)
forall e s a.
Parser e s a -> (# ByteArray#, Int#, Int# #) -> ST# s (Result# e a)
runParser (a -> Parser s e b
g a
y) (# ByteArray#
arr, Int#
b, Int#
c #) State# e
s1
    )

sequenceIntToIntPair ::
  forall
    s
    e
    (a :: TYPE 'IntRep)
    (b :: TYPE ('TupleRep '[ 'IntRep, 'IntRep])).
  Parser s e a ->
  Parser s e b ->
  Parser s e b
{-# INLINE sequenceIntToIntPair #-}
sequenceIntToIntPair :: forall e s (a :: TYPE 'IntRep)
       (b :: TYPE ('TupleRep '[ 'IntRep, 'IntRep])).
Parser e s a -> Parser e s b -> Parser e s b
sequenceIntToIntPair (Parser (# ByteArray#, Int#, Int# #) -> ST# e (Result# s a)
f) (Parser (# ByteArray#, Int#, Int# #) -> ST# e (Result# s b)
g) =
  ((# ByteArray#, Int#, Int# #) -> ST# e (Result# s b))
-> Parser s e b
forall a b c.
((# ByteArray#, Int#, Int# #) -> ST# b (Result# a c))
-> Parser a b c
Parser
    ( \x :: (# ByteArray#, Int#, Int# #)
x@(# ByteArray#
arr, Int#
_, Int#
_ #) State# e
s0 -> case (# ByteArray#, Int#, Int# #) -> ST# e (Result# s a)
f (# ByteArray#, Int#, Int# #)
x State# e
s0 of
        (# State# e
s1, Result# s a
r0 #) -> case Result# s a
r0 of
          (# s
e | #) -> (# State# e
s1, (# s
e | #) #)
          (# | (# a
_, Int#
b, Int#
c #) #) -> (# ByteArray#, Int#, Int# #) -> ST# e (Result# s b)
g (# ByteArray#
arr, Int#
b, Int#
c #) State# e
s1
    )

bindFromIntToInt5 ::
  forall
    s
    e
    (a :: TYPE 'IntRep)
    (b :: TYPE ('TupleRep '[ 'IntRep, 'IntRep, 'IntRep, 'IntRep, 'IntRep])).
  Parser s e a ->
  (a -> Parser s e b) ->
  Parser s e b
{-# INLINE bindFromIntToInt5 #-}
bindFromIntToInt5 :: forall e s (a :: TYPE 'IntRep)
       (b :: TYPE
               ('TupleRep '[ 'IntRep, 'IntRep, 'IntRep, 'IntRep, 'IntRep])).
Parser e s a -> (a -> Parser e s b) -> Parser e s b
bindFromIntToInt5 (Parser (# ByteArray#, Int#, Int# #) -> ST# e (Result# s a)
f) a -> Parser s e b
g =
  ((# ByteArray#, Int#, Int# #) -> ST# e (Result# s b))
-> Parser s e b
forall a b c.
((# ByteArray#, Int#, Int# #) -> ST# b (Result# a c))
-> Parser a b c
Parser
    ( \x :: (# ByteArray#, Int#, Int# #)
x@(# ByteArray#
arr, Int#
_, Int#
_ #) State# e
s0 -> case (# ByteArray#, Int#, Int# #) -> ST# e (Result# s a)
f (# ByteArray#, Int#, Int# #)
x State# e
s0 of
        (# State# e
s1, Result# s a
r0 #) -> case Result# s a
r0 of
          (# s
e | #) -> (# State# e
s1, (# s
e | #) #)
          (# | (# a
y, Int#
b, Int#
c #) #) ->
            Parser s e b -> (# ByteArray#, Int#, Int# #) -> ST# e (Result# s b)
forall e s a.
Parser e s a -> (# ByteArray#, Int#, Int# #) -> ST# s (Result# e a)
runParser (a -> Parser s e b
g a
y) (# ByteArray#
arr, Int#
b, Int#
c #) State# e
s1
    )

sequenceIntToInt5 ::
  forall
    s
    e
    (a :: TYPE 'IntRep)
    (b :: TYPE ('TupleRep '[ 'IntRep, 'IntRep, 'IntRep, 'IntRep, 'IntRep])).
  Parser s e a ->
  Parser s e b ->
  Parser s e b
{-# INLINE sequenceIntToInt5 #-}
sequenceIntToInt5 :: forall e s (a :: TYPE 'IntRep)
       (b :: TYPE
               ('TupleRep '[ 'IntRep, 'IntRep, 'IntRep, 'IntRep, 'IntRep])).
Parser e s a -> Parser e s b -> Parser e s b
sequenceIntToInt5 (Parser (# ByteArray#, Int#, Int# #) -> ST# e (Result# s a)
f) (Parser (# ByteArray#, Int#, Int# #) -> ST# e (Result# s b)
g) =
  ((# ByteArray#, Int#, Int# #) -> ST# e (Result# s b))
-> Parser s e b
forall a b c.
((# ByteArray#, Int#, Int# #) -> ST# b (Result# a c))
-> Parser a b c
Parser
    ( \x :: (# ByteArray#, Int#, Int# #)
x@(# ByteArray#
arr, Int#
_, Int#
_ #) State# e
s0 -> case (# ByteArray#, Int#, Int# #) -> ST# e (Result# s a)
f (# ByteArray#, Int#, Int# #)
x State# e
s0 of
        (# State# e
s1, Result# s a
r0 #) -> case Result# s a
r0 of
          (# s
e | #) -> (# State# e
s1, (# s
e | #) #)
          (# | (# a
_, Int#
b, Int#
c #) #) -> (# ByteArray#, Int#, Int# #) -> ST# e (Result# s b)
g (# ByteArray#
arr, Int#
b, Int#
c #) State# e
s1
    )

bindFromLiftedToIntPair ::
  forall
    s
    e
    (a :: TYPE LiftedRep)
    (b :: TYPE ('TupleRep '[ 'IntRep, 'IntRep])).
  Parser s e a ->
  (a -> Parser s e b) ->
  Parser s e b
{-# INLINE bindFromLiftedToIntPair #-}
bindFromLiftedToIntPair :: forall e s a (b :: TYPE ('TupleRep '[ 'IntRep, 'IntRep])).
Parser e s a -> (a -> Parser e s b) -> Parser e s b
bindFromLiftedToIntPair (Parser (# ByteArray#, Int#, Int# #) -> ST# e (Result# s a)
f) a -> Parser s e b
g =
  ((# ByteArray#, Int#, Int# #) -> ST# e (Result# s b))
-> Parser s e b
forall a b c.
((# ByteArray#, Int#, Int# #) -> ST# b (Result# a c))
-> Parser a b c
Parser
    ( \x :: (# ByteArray#, Int#, Int# #)
x@(# ByteArray#
arr, Int#
_, Int#
_ #) State# e
s0 -> case (# ByteArray#, Int#, Int# #) -> ST# e (Result# s a)
f (# ByteArray#, Int#, Int# #)
x State# e
s0 of
        (# State# e
s1, Result# s a
r0 #) -> case Result# s a
r0 of
          (# s
e | #) -> (# State# e
s1, (# s
e | #) #)
          (# | (# a
y, Int#
b, Int#
c #) #) ->
            Parser s e b -> (# ByteArray#, Int#, Int# #) -> ST# e (Result# s b)
forall e s a.
Parser e s a -> (# ByteArray#, Int#, Int# #) -> ST# s (Result# e a)
runParser (a -> Parser s e b
g a
y) (# ByteArray#
arr, Int#
b, Int#
c #) State# e
s1
    )

sequenceLiftedToIntPair ::
  forall
    s
    e
    (a :: TYPE LiftedRep)
    (b :: TYPE ('TupleRep '[ 'IntRep, 'IntRep])).
  Parser s e a ->
  Parser s e b ->
  Parser s e b
{-# INLINE sequenceLiftedToIntPair #-}
sequenceLiftedToIntPair :: forall e s a (b :: TYPE ('TupleRep '[ 'IntRep, 'IntRep])).
Parser e s a -> Parser e s b -> Parser e s b
sequenceLiftedToIntPair (Parser (# ByteArray#, Int#, Int# #) -> ST# e (Result# s a)
f) (Parser (# ByteArray#, Int#, Int# #) -> ST# e (Result# s b)
g) =
  ((# ByteArray#, Int#, Int# #) -> ST# e (Result# s b))
-> Parser s e b
forall a b c.
((# ByteArray#, Int#, Int# #) -> ST# b (Result# a c))
-> Parser a b c
Parser
    ( \x :: (# ByteArray#, Int#, Int# #)
x@(# ByteArray#
arr, Int#
_, Int#
_ #) State# e
s0 -> case (# ByteArray#, Int#, Int# #) -> ST# e (Result# s a)
f (# ByteArray#, Int#, Int# #)
x State# e
s0 of
        (# State# e
s1, Result# s a
r0 #) -> case Result# s a
r0 of
          (# s
e | #) -> (# State# e
s1, (# s
e | #) #)
          (# | (# a
_, Int#
b, Int#
c #) #) -> (# ByteArray#, Int#, Int# #) -> ST# e (Result# s b)
g (# ByteArray#
arr, Int#
b, Int#
c #) State# e
s1
    )

bindFromLiftedToInt5 ::
  forall
    s
    e
    (a :: TYPE LiftedRep)
    (b :: TYPE ('TupleRep '[ 'IntRep, 'IntRep, 'IntRep, 'IntRep, 'IntRep])).
  Parser s e a ->
  (a -> Parser s e b) ->
  Parser s e b
{-# INLINE bindFromLiftedToInt5 #-}
bindFromLiftedToInt5 :: forall e s a
       (b :: TYPE
               ('TupleRep '[ 'IntRep, 'IntRep, 'IntRep, 'IntRep, 'IntRep])).
Parser e s a -> (a -> Parser e s b) -> Parser e s b
bindFromLiftedToInt5 (Parser (# ByteArray#, Int#, Int# #) -> ST# e (Result# s a)
f) a -> Parser s e b
g =
  ((# ByteArray#, Int#, Int# #) -> ST# e (Result# s b))
-> Parser s e b
forall a b c.
((# ByteArray#, Int#, Int# #) -> ST# b (Result# a c))
-> Parser a b c
Parser
    ( \x :: (# ByteArray#, Int#, Int# #)
x@(# ByteArray#
arr, Int#
_, Int#
_ #) State# e
s0 -> case (# ByteArray#, Int#, Int# #) -> ST# e (Result# s a)
f (# ByteArray#, Int#, Int# #)
x State# e
s0 of
        (# State# e
s1, Result# s a
r0 #) -> case Result# s a
r0 of
          (# s
e | #) -> (# State# e
s1, (# s
e | #) #)
          (# | (# a
y, Int#
b, Int#
c #) #) ->
            Parser s e b -> (# ByteArray#, Int#, Int# #) -> ST# e (Result# s b)
forall e s a.
Parser e s a -> (# ByteArray#, Int#, Int# #) -> ST# s (Result# e a)
runParser (a -> Parser s e b
g a
y) (# ByteArray#
arr, Int#
b, Int#
c #) State# e
s1
    )

sequenceLiftedToInt5 ::
  forall
    s
    e
    (a :: TYPE LiftedRep)
    (b :: TYPE ('TupleRep '[ 'IntRep, 'IntRep, 'IntRep, 'IntRep, 'IntRep])).
  Parser s e a ->
  Parser s e b ->
  Parser s e b
{-# INLINE sequenceLiftedToInt5 #-}
sequenceLiftedToInt5 :: forall e s a
       (b :: TYPE
               ('TupleRep '[ 'IntRep, 'IntRep, 'IntRep, 'IntRep, 'IntRep])).
Parser e s a -> Parser e s b -> Parser e s b
sequenceLiftedToInt5 (Parser (# ByteArray#, Int#, Int# #) -> ST# e (Result# s a)
f) (Parser (# ByteArray#, Int#, Int# #) -> ST# e (Result# s b)
g) =
  ((# ByteArray#, Int#, Int# #) -> ST# e (Result# s b))
-> Parser s e b
forall a b c.
((# ByteArray#, Int#, Int# #) -> ST# b (Result# a c))
-> Parser a b c
Parser
    ( \x :: (# ByteArray#, Int#, Int# #)
x@(# ByteArray#
arr, Int#
_, Int#
_ #) State# e
s0 -> case (# ByteArray#, Int#, Int# #) -> ST# e (Result# s a)
f (# ByteArray#, Int#, Int# #)
x State# e
s0 of
        (# State# e
s1, Result# s a
r0 #) -> case Result# s a
r0 of
          (# s
e | #) -> (# State# e
s1, (# s
e | #) #)
          (# | (# a
_, Int#
b, Int#
c #) #) -> (# ByteArray#, Int#, Int# #) -> ST# e (Result# s b)
g (# ByteArray#
arr, Int#
b, Int#
c #) State# e
s1
    )

bindFromLiftedToInt ::
  forall
    s
    e
    (a :: TYPE LiftedRep)
    (b :: TYPE 'IntRep).
  Parser s e a ->
  (a -> Parser s e b) ->
  Parser s e b
{-# INLINE bindFromLiftedToInt #-}
bindFromLiftedToInt :: forall e s a (b :: TYPE 'IntRep).
Parser e s a -> (a -> Parser e s b) -> Parser e s b
bindFromLiftedToInt (Parser (# ByteArray#, Int#, Int# #) -> ST# e (Result# s a)
f) a -> Parser s e b
g =
  ((# ByteArray#, Int#, Int# #) -> ST# e (Result# s b))
-> Parser s e b
forall a b c.
((# ByteArray#, Int#, Int# #) -> ST# b (Result# a c))
-> Parser a b c
Parser
    ( \x :: (# ByteArray#, Int#, Int# #)
x@(# ByteArray#
arr, Int#
_, Int#
_ #) State# e
s0 -> case (# ByteArray#, Int#, Int# #) -> ST# e (Result# s a)
f (# ByteArray#, Int#, Int# #)
x State# e
s0 of
        (# State# e
s1, Result# s a
r0 #) -> case Result# s a
r0 of
          (# s
e | #) -> (# State# e
s1, (# s
e | #) #)
          (# | (# a
y, Int#
b, Int#
c #) #) ->
            Parser s e b -> (# ByteArray#, Int#, Int# #) -> ST# e (Result# s b)
forall e s a.
Parser e s a -> (# ByteArray#, Int#, Int# #) -> ST# s (Result# e a)
runParser (a -> Parser s e b
g a
y) (# ByteArray#
arr, Int#
b, Int#
c #) State# e
s1
    )

sequenceLiftedToInt ::
  forall
    s
    e
    (a :: TYPE LiftedRep)
    (b :: TYPE 'IntRep).
  Parser s e a ->
  Parser s e b ->
  Parser s e b
{-# INLINE sequenceLiftedToInt #-}
sequenceLiftedToInt :: forall e s a (b :: TYPE 'IntRep).
Parser e s a -> Parser e s b -> Parser e s b
sequenceLiftedToInt (Parser (# ByteArray#, Int#, Int# #) -> ST# e (Result# s a)
f) (Parser (# ByteArray#, Int#, Int# #) -> ST# e (Result# s b)
g) =
  ((# ByteArray#, Int#, Int# #) -> ST# e (Result# s b))
-> Parser s e b
forall a b c.
((# ByteArray#, Int#, Int# #) -> ST# b (Result# a c))
-> Parser a b c
Parser
    ( \x :: (# ByteArray#, Int#, Int# #)
x@(# ByteArray#
arr, Int#
_, Int#
_ #) State# e
s0 -> case (# ByteArray#, Int#, Int# #) -> ST# e (Result# s a)
f (# ByteArray#, Int#, Int# #)
x State# e
s0 of
        (# State# e
s1, Result# s a
r0 #) -> case Result# s a
r0 of
          (# s
e | #) -> (# State# e
s1, (# s
e | #) #)
          (# | (# a
_, Int#
b, Int#
c #) #) -> (# ByteArray#, Int#, Int# #) -> ST# e (Result# s b)
g (# ByteArray#
arr, Int#
b, Int#
c #) State# e
s1
    )