{-# OPTIONS_GHC -Wno-deprecations #-}
module Streamly.Internal.Data.Array.Stream
{-# DEPRECATED "Please use \"Streamly.Internal.Data.Array\" instead." #-}
(
Array.chunksOf
, Array.pinnedChunksOf
, Array.bufferChunks
, Array.concat
, Array.flattenArrays
, Array.concatRev
, Array.flattenArraysRev
, Array.interpose
, Array.interposeSuffix
, Array.intercalateSuffix
, unlines
, foldBreak
, foldBreakD
, parseBreak
, K.parseBreakChunks
, K.parseChunks
, runArrayFold
, runArrayFoldBreak
, runArrayParserDBreak
, runArrayFoldMany
, toArray
, lpackArraysChunksOf
, compact
, splitOn
, splitOnSuffix
)
where
#include "ArrayMacros.h"
#include "inline.hs"
import Data.Bifunctor (second)
import Control.Exception (assert)
import Control.Monad.IO.Class (MonadIO(..))
import Data.Proxy (Proxy(..))
import Data.Word (Word8)
import Streamly.Internal.Data.Unbox (Unbox(..))
import Fusion.Plugin.Types (Fuse(..))
import GHC.Exts (SpecConstrAnnotation(..))
import GHC.Types (SPEC(..))
import Prelude hiding (null, last, (!!), read, concat, unlines)
import Streamly.Data.Fold (Fold)
import Streamly.Internal.Data.Array.Type (Array(..))
import Streamly.Internal.Data.Fold.Chunked (ChunkFold(..))
import Streamly.Internal.Data.Parser (ParseError(..))
import Streamly.Internal.Data.Stream (Stream)
import Streamly.Internal.Data.StreamK (StreamK, fromStream, toStream)
import Streamly.Internal.Data.SVar.Type (adaptState, defState)
import qualified Streamly.Internal.Data.Array as A
import qualified Streamly.Internal.Data.Array as Array
import qualified Streamly.Internal.Data.Parser as PR
import qualified Streamly.Internal.Data.Parser as PRD
(Parser(..), Initial(..))
import qualified Streamly.Internal.Data.Stream as D
import qualified Streamly.Internal.Data.StreamK as K
{-# INLINE_NORMAL unlines #-}
unlines :: forall m a. (MonadIO m, Unbox a)
=> a -> D.Stream m (Array a) -> D.Stream m a
unlines :: forall (m :: * -> *) a.
(MonadIO m, Unbox a) =>
a -> Stream m (Array a) -> Stream m a
unlines = a -> Stream m (Array a) -> Stream m a
forall (m :: * -> *) a.
(Monad m, Unbox a) =>
a -> Stream m (Array a) -> Stream m a
Array.interposeSuffix
{-# INLINE_NORMAL lpackArraysChunksOf #-}
lpackArraysChunksOf :: (MonadIO m, Unbox a)
=> Int -> Fold m (Array a) () -> Fold m (Array a) ()
lpackArraysChunksOf :: forall (m :: * -> *) a.
(MonadIO m, Unbox a) =>
Int -> Fold m (Array a) () -> Fold m (Array a) ()
lpackArraysChunksOf = Int -> Fold m (Array a) () -> Fold m (Array a) ()
forall (m :: * -> *) a.
(MonadIO m, Unbox a) =>
Int -> Fold m (Array a) () -> Fold m (Array a) ()
Array.lCompactGE
{-# INLINE compact #-}
compact :: (MonadIO m, Unbox a)
=> Int -> Stream m (Array a) -> Stream m (Array a)
compact :: forall (m :: * -> *) a.
(MonadIO m, Unbox a) =>
Int -> Stream m (Array a) -> Stream m (Array a)
compact = Int -> Stream m (Array a) -> Stream m (Array a)
forall (m :: * -> *) a.
(MonadIO m, Unbox a) =>
Int -> Stream m (Array a) -> Stream m (Array a)
Array.compactLE
{-# INLINE toArray #-}
toArray :: (MonadIO m, Unbox a) => Stream m (Array a) -> m (Array a)
toArray :: forall (m :: * -> *) a.
(MonadIO m, Unbox a) =>
Stream m (Array a) -> m (Array a)
toArray = Stream m (Array a) -> m (Array a)
forall (m :: * -> *) a.
(MonadIO m, Unbox a) =>
Stream m (Array a) -> m (Array a)
Array.fromChunks
{-# INLINE splitOn #-}
splitOn
:: (MonadIO m)
=> Word8
-> Stream m (Array Word8)
-> Stream m (Array Word8)
splitOn :: forall (m :: * -> *).
MonadIO m =>
Word8 -> Stream m (Array Word8) -> Stream m (Array Word8)
splitOn = Word8 -> Stream m (Array Word8) -> Stream m (Array Word8)
forall (m :: * -> *).
MonadIO m =>
Word8 -> Stream m (Array Word8) -> Stream m (Array Word8)
Array.compactOnByte
{-# INLINE splitOnSuffix #-}
splitOnSuffix
:: (MonadIO m)
=> Word8
-> Stream m (Array Word8)
-> Stream m (Array Word8)
splitOnSuffix :: forall (m :: * -> *).
MonadIO m =>
Word8 -> Stream m (Array Word8) -> Stream m (Array Word8)
splitOnSuffix = Word8 -> Stream m (Array Word8) -> Stream m (Array Word8)
forall (m :: * -> *).
MonadIO m =>
Word8 -> Stream m (Array Word8) -> Stream m (Array Word8)
Array.compactOnByteSuffix
{-# INLINE_NORMAL foldBreakD #-}
foldBreakD :: forall m a b. (MonadIO m, Unbox a) =>
Fold m a b -> D.Stream m (Array a) -> m (b, D.Stream m (Array a))
foldBreakD :: forall (m :: * -> *) a b.
(MonadIO m, Unbox a) =>
Fold m a b -> Stream m (Array a) -> m (b, Stream m (Array a))
foldBreakD = Fold m a b -> Stream m (Array a) -> m (b, Stream m (Array a))
forall (m :: * -> *) a b.
(MonadIO m, Unbox a) =>
Fold m a b -> Stream m (Array a) -> m (b, Stream m (Array a))
Array.foldBreakChunks
{-# INLINE_NORMAL foldBreak #-}
foldBreak ::
(MonadIO m, Unbox a)
=> Fold m a b
-> StreamK m (A.Array a)
-> m (b, StreamK m (A.Array a))
foldBreak :: forall (m :: * -> *) a b.
(MonadIO m, Unbox a) =>
Fold m a b -> StreamK m (Array a) -> m (b, StreamK m (Array a))
foldBreak = Fold m a b -> StreamK m (Array a) -> m (b, StreamK m (Array a))
forall (m :: * -> *) a b.
(MonadIO m, Unbox a) =>
Fold m a b -> StreamK m (Array a) -> m (b, StreamK m (Array a))
Array.foldBreakChunksK
{-# INLINE takeArrayListRev #-}
takeArrayListRev :: forall a. Unbox a => Int -> [Array a] -> [Array a]
takeArrayListRev :: forall a. Unbox a => Int -> [Array a] -> [Array a]
takeArrayListRev = Int -> [Array a] -> [Array a]
forall a. Unbox a => Int -> [Array a] -> [Array a]
go
where
go :: Int -> [Array a] -> [Array a]
go Int
_ [] = []
go Int
n [Array a]
_ | Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
0 = []
go Int
n (Array a
x:[Array a]
xs) =
let len :: Int
len = Array a -> Int
forall a. Unbox a => Array a -> Int
Array.length Array a
x
in if Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
len
then Array a
x Array a -> [Array a] -> [Array a]
forall a. a -> [a] -> [a]
: Int -> [Array a] -> [Array a]
go (Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
len) [Array a]
xs
else if Int
n Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
len
then [Array a
x]
else let !(Array MutByteArray
contents Int
_ Int
end) = Array a
x
!start :: Int
start = Int
end Int -> Int -> Int
forall a. Num a => a -> a -> a
- (Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
* SIZE_OF(a))
in [MutByteArray -> Int -> Int -> Array a
forall a. MutByteArray -> Int -> Int -> Array a
Array MutByteArray
contents Int
start Int
end]
{-# INLINE splitAtArrayListRev #-}
splitAtArrayListRev ::
forall a. Unbox a => Int -> [Array a] -> ([Array a],[Array a])
splitAtArrayListRev :: forall a. Unbox a => Int -> [Array a] -> ([Array a], [Array a])
splitAtArrayListRev Int
n [Array a]
ls
| Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
0 = ([], [Array a]
ls)
| Bool
otherwise = Int -> [Array a] -> ([Array a], [Array a])
go Int
n [Array a]
ls
where
go :: Int -> [Array a] -> ([Array a], [Array a])
go :: Int -> [Array a] -> ([Array a], [Array a])
go Int
_ [] = ([], [])
go Int
m (Array a
x:[Array a]
xs) =
let len :: Int
len = Array a -> Int
forall a. Unbox a => Array a -> Int
Array.length Array a
x
([Array a]
xs', [Array a]
xs'') = Int -> [Array a] -> ([Array a], [Array a])
go (Int
m Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
len) [Array a]
xs
in if Int
m Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
len
then (Array a
xArray a -> [Array a] -> [Array a]
forall a. a -> [a] -> [a]
:[Array a]
xs', [Array a]
xs'')
else if Int
m Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
len
then ([Array a
x],[Array a]
xs)
else let !(Array MutByteArray
contents Int
start Int
end) = Array a
x
end1 :: Int
end1 = Int
end Int -> Int -> Int
forall a. Num a => a -> a -> a
- (Int
m Int -> Int -> Int
forall a. Num a => a -> a -> a
* SIZE_OF(a))
arr2 :: Array a
arr2 = MutByteArray -> Int -> Int -> Array a
forall a. MutByteArray -> Int -> Int -> Array a
Array MutByteArray
contents Int
start Int
end1
arr1 :: Array a
arr1 = MutByteArray -> Int -> Int -> Array a
forall a. MutByteArray -> Int -> Int -> Array a
Array MutByteArray
contents Int
end1 Int
end
in ([Array a
forall {a}. Array a
arr1], Array a
forall {a}. Array a
arr2Array a -> [Array a] -> [Array a]
forall a. a -> [a] -> [a]
:[Array a]
xs)
{-# ANN type List NoSpecConstr #-}
newtype List a = List {forall a. List a -> [a]
getList :: [a]}
{-# INLINE_NORMAL parseBreak #-}
parseBreak ::
(MonadIO m, Unbox a)
=> PR.Parser a m b
-> StreamK m (A.Array a)
-> m (Either ParseError b, StreamK m (A.Array a))
parseBreak :: forall (m :: * -> *) a b.
(MonadIO m, Unbox a) =>
Parser a m b
-> StreamK m (Array a)
-> m (Either ParseError b, StreamK m (Array a))
parseBreak = Parser a m b
-> StreamK m (Array a)
-> m (Either ParseError b, StreamK m (Array a))
forall (m :: * -> *) a b.
(MonadIO m, Unbox a) =>
Parser a m b
-> StreamK m (Array a)
-> m (Either ParseError b, StreamK m (Array a))
Array.parseBreakChunksK
{-# INLINE_NORMAL runArrayParserDBreak #-}
runArrayParserDBreak ::
forall m a b. (MonadIO m, Unbox a)
=> PRD.Parser (Array a) m b
-> D.Stream m (Array.Array a)
-> m (Either ParseError b, D.Stream m (Array.Array a))
runArrayParserDBreak :: forall (m :: * -> *) a b.
(MonadIO m, Unbox a) =>
Parser (Array a) m b
-> Stream m (Array a)
-> m (Either ParseError b, Stream m (Array a))
runArrayParserDBreak
(PRD.Parser s -> Array a -> m (Step s b)
pstep m (Initial s b)
initial s -> m (Step s b)
extract)
stream :: Stream m (Array a)
stream@(D.Stream State StreamK m (Array a) -> s -> m (Step s (Array a))
step s
state) = do
Initial s b
res <- m (Initial s b)
initial
case Initial s b
res of
PRD.IPartial s
s -> SPEC
-> s
-> List (Array a)
-> s
-> m (Either ParseError b, Stream m (Array a))
go SPEC
SPEC s
state ([Array a] -> List (Array a)
forall a. [a] -> List a
List []) s
s
PRD.IDone b
b -> (Either ParseError b, Stream m (Array a))
-> m (Either ParseError b, Stream m (Array a))
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (b -> Either ParseError b
forall a b. b -> Either a b
Right b
b, Stream m (Array a)
stream)
PRD.IError String
err -> (Either ParseError b, Stream m (Array a))
-> m (Either ParseError b, Stream m (Array a))
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (ParseError -> Either ParseError b
forall a b. a -> Either a b
Left (String -> ParseError
ParseError String
err), Stream m (Array a)
stream)
where
go :: SPEC
-> s
-> List (Array a)
-> s
-> m (Either ParseError b, Stream m (Array a))
go SPEC
_ s
st List (Array a)
backBuf !s
pst = do
Step s (Array a)
r <- State StreamK m (Array a) -> s -> m (Step s (Array a))
step State StreamK m (Array a)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. State t m a
defState s
st
case Step s (Array a)
r of
D.Yield Array a
x s
s -> SPEC
-> [Array a]
-> s
-> List (Array a)
-> s
-> m (Either ParseError b, Stream m (Array a))
gobuf SPEC
SPEC [Array a
x] s
s List (Array a)
backBuf s
pst
D.Skip s
s -> SPEC
-> s
-> List (Array a)
-> s
-> m (Either ParseError b, Stream m (Array a))
go SPEC
SPEC s
s List (Array a)
backBuf s
pst
Step s (Array a)
D.Stop -> List (Array a) -> s -> m (Either ParseError b, Stream m (Array a))
forall {m :: * -> *}.
Applicative m =>
List (Array a) -> s -> m (Either ParseError b, Stream m (Array a))
goStop List (Array a)
backBuf s
pst
gobuf :: SPEC
-> [Array a]
-> s
-> List (Array a)
-> s
-> m (Either ParseError b, Stream m (Array a))
gobuf !SPEC
_ [] s
s List (Array a)
backBuf !s
pst = SPEC
-> s
-> List (Array a)
-> s
-> m (Either ParseError b, Stream m (Array a))
go SPEC
SPEC s
s List (Array a)
backBuf s
pst
gobuf !SPEC
_ (Array a
x:[Array a]
xs) s
s List (Array a)
backBuf !s
pst = do
Step s b
pRes <- s -> Array a -> m (Step s b)
pstep s
pst Array a
x
case Step s b
pRes of
PR.Partial Int
0 s
pst1 ->
SPEC
-> [Array a]
-> s
-> List (Array a)
-> s
-> m (Either ParseError b, Stream m (Array a))
gobuf SPEC
SPEC [Array a]
xs s
s ([Array a] -> List (Array a)
forall a. [a] -> List a
List []) s
pst1
PR.Partial Int
n s
pst1 -> do
Bool -> m () -> m ()
forall a. (?callStack::CallStack) => Bool -> a -> a
assert
(Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= [Int] -> Int
forall a. Num a => [a] -> a
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
sum ((Array a -> Int) -> [Array a] -> [Int]
forall a b. (a -> b) -> [a] -> [b]
map Array a -> Int
forall a. Unbox a => Array a -> Int
Array.length (Array a
xArray a -> [Array a] -> [Array a]
forall a. a -> [a] -> [a]
:List (Array a) -> [Array a]
forall a. List a -> [a]
getList List (Array a)
backBuf)))
(() -> m ()
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return ())
let src0 :: [Array a]
src0 = Int -> [Array a] -> [Array a]
forall a. Unbox a => Int -> [Array a] -> [Array a]
takeArrayListRev Int
n (Array a
xArray a -> [Array a] -> [Array a]
forall a. a -> [a] -> [a]
:List (Array a) -> [Array a]
forall a. List a -> [a]
getList List (Array a)
backBuf)
src :: [Array a]
src = [Array a] -> [Array a]
forall a. [a] -> [a]
Prelude.reverse [Array a]
src0 [Array a] -> [Array a] -> [Array a]
forall a. [a] -> [a] -> [a]
++ [Array a]
xs
SPEC
-> [Array a]
-> s
-> List (Array a)
-> s
-> m (Either ParseError b, Stream m (Array a))
gobuf SPEC
SPEC [Array a]
src s
s ([Array a] -> List (Array a)
forall a. [a] -> List a
List []) s
pst1
PR.Continue Int
0 s
pst1 ->
SPEC
-> [Array a]
-> s
-> List (Array a)
-> s
-> m (Either ParseError b, Stream m (Array a))
gobuf SPEC
SPEC [Array a]
xs s
s ([Array a] -> List (Array a)
forall a. [a] -> List a
List (Array a
xArray a -> [Array a] -> [Array a]
forall a. a -> [a] -> [a]
:List (Array a) -> [Array a]
forall a. List a -> [a]
getList List (Array a)
backBuf)) s
pst1
PR.Continue Int
n s
pst1 -> do
Bool -> m () -> m ()
forall a. (?callStack::CallStack) => Bool -> a -> a
assert
(Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= [Int] -> Int
forall a. Num a => [a] -> a
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
sum ((Array a -> Int) -> [Array a] -> [Int]
forall a b. (a -> b) -> [a] -> [b]
map Array a -> Int
forall a. Unbox a => Array a -> Int
Array.length (Array a
xArray a -> [Array a] -> [Array a]
forall a. a -> [a] -> [a]
:List (Array a) -> [Array a]
forall a. List a -> [a]
getList List (Array a)
backBuf)))
(() -> m ()
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return ())
let ([Array a]
src0, [Array a]
buf1) = Int -> [Array a] -> ([Array a], [Array a])
forall a. Unbox a => Int -> [Array a] -> ([Array a], [Array a])
splitAtArrayListRev Int
n (Array a
xArray a -> [Array a] -> [Array a]
forall a. a -> [a] -> [a]
:List (Array a) -> [Array a]
forall a. List a -> [a]
getList List (Array a)
backBuf)
src :: [Array a]
src = [Array a] -> [Array a]
forall a. [a] -> [a]
Prelude.reverse [Array a]
src0 [Array a] -> [Array a] -> [Array a]
forall a. [a] -> [a] -> [a]
++ [Array a]
xs
SPEC
-> [Array a]
-> s
-> List (Array a)
-> s
-> m (Either ParseError b, Stream m (Array a))
gobuf SPEC
SPEC [Array a]
src s
s ([Array a] -> List (Array a)
forall a. [a] -> List a
List [Array a]
buf1) s
pst1
PR.Done Int
0 b
b -> do
let str :: Stream m (Array a)
str = Stream m (Array a) -> Stream m (Array a) -> Stream m (Array a)
forall (m :: * -> *) a.
Monad m =>
Stream m a -> Stream m a -> Stream m a
D.append ([Array a] -> Stream m (Array a)
forall (m :: * -> *) a. Applicative m => [a] -> Stream m a
D.fromList [Array a]
xs) ((State StreamK m (Array a) -> s -> m (Step s (Array a)))
-> s -> Stream m (Array a)
forall (m :: * -> *) a s.
(State StreamK m a -> s -> m (Step s a)) -> s -> Stream m a
D.Stream State StreamK m (Array a) -> s -> m (Step s (Array a))
step s
s)
(Either ParseError b, Stream m (Array a))
-> m (Either ParseError b, Stream m (Array a))
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (b -> Either ParseError b
forall a b. b -> Either a b
Right b
b, Stream m (Array a)
str)
PR.Done Int
n b
b -> do
Bool -> m () -> m ()
forall a. (?callStack::CallStack) => Bool -> a -> a
assert
(Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= [Int] -> Int
forall a. Num a => [a] -> a
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
sum ((Array a -> Int) -> [Array a] -> [Int]
forall a b. (a -> b) -> [a] -> [b]
map Array a -> Int
forall a. Unbox a => Array a -> Int
Array.length (Array a
xArray a -> [Array a] -> [Array a]
forall a. a -> [a] -> [a]
:List (Array a) -> [Array a]
forall a. List a -> [a]
getList List (Array a)
backBuf)))
(() -> m ()
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return ())
let src0 :: [Array a]
src0 = Int -> [Array a] -> [Array a]
forall a. Unbox a => Int -> [Array a] -> [Array a]
takeArrayListRev Int
n (Array a
xArray a -> [Array a] -> [Array a]
forall a. a -> [a] -> [a]
:List (Array a) -> [Array a]
forall a. List a -> [a]
getList List (Array a)
backBuf)
src :: [Array a]
src = [Array a] -> [Array a]
forall a. [a] -> [a]
Prelude.reverse [Array a]
src0 [Array a] -> [Array a] -> [Array a]
forall a. [a] -> [a] -> [a]
++ [Array a]
xs
(Either ParseError b, Stream m (Array a))
-> m (Either ParseError b, Stream m (Array a))
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (b -> Either ParseError b
forall a b. b -> Either a b
Right b
b, Stream m (Array a) -> Stream m (Array a) -> Stream m (Array a)
forall (m :: * -> *) a.
Monad m =>
Stream m a -> Stream m a -> Stream m a
D.append ([Array a] -> Stream m (Array a)
forall (m :: * -> *) a. Applicative m => [a] -> Stream m a
D.fromList [Array a]
src) ((State StreamK m (Array a) -> s -> m (Step s (Array a)))
-> s -> Stream m (Array a)
forall (m :: * -> *) a s.
(State StreamK m a -> s -> m (Step s a)) -> s -> Stream m a
D.Stream State StreamK m (Array a) -> s -> m (Step s (Array a))
step s
s))
PR.Error String
err -> do
let src0 :: [Array a]
src0 = Array a
xArray a -> [Array a] -> [Array a]
forall a. a -> [a] -> [a]
:List (Array a) -> [Array a]
forall a. List a -> [a]
getList List (Array a)
backBuf
src :: [Array a]
src = [Array a] -> [Array a]
forall a. [a] -> [a]
Prelude.reverse [Array a]
src0 [Array a] -> [Array a] -> [Array a]
forall a. [a] -> [a] -> [a]
++ Array a
xArray a -> [Array a] -> [Array a]
forall a. a -> [a] -> [a]
:[Array a]
xs
strm :: Stream m (Array a)
strm = Stream m (Array a) -> Stream m (Array a) -> Stream m (Array a)
forall (m :: * -> *) a.
Monad m =>
Stream m a -> Stream m a -> Stream m a
D.append ([Array a] -> Stream m (Array a)
forall (m :: * -> *) a. Applicative m => [a] -> Stream m a
D.fromList [Array a]
src) ((State StreamK m (Array a) -> s -> m (Step s (Array a)))
-> s -> Stream m (Array a)
forall (m :: * -> *) a s.
(State StreamK m a -> s -> m (Step s a)) -> s -> Stream m a
D.Stream State StreamK m (Array a) -> s -> m (Step s (Array a))
step s
s)
(Either ParseError b, Stream m (Array a))
-> m (Either ParseError b, Stream m (Array a))
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (ParseError -> Either ParseError b
forall a b. a -> Either a b
Left (String -> ParseError
ParseError String
err), Stream m (Array a)
strm)
goExtract :: SPEC
-> [Array a]
-> List (Array a)
-> s
-> m (Either ParseError b, Stream m (Array a))
goExtract SPEC
_ [] List (Array a)
backBuf !s
pst = List (Array a) -> s -> m (Either ParseError b, Stream m (Array a))
goStop List (Array a)
backBuf s
pst
goExtract SPEC
_ (Array a
x:[Array a]
xs) List (Array a)
backBuf !s
pst = do
Step s b
pRes <- s -> Array a -> m (Step s b)
pstep s
pst Array a
x
case Step s b
pRes of
PR.Partial Int
0 s
pst1 ->
SPEC
-> [Array a]
-> List (Array a)
-> s
-> m (Either ParseError b, Stream m (Array a))
goExtract SPEC
SPEC [Array a]
xs ([Array a] -> List (Array a)
forall a. [a] -> List a
List []) s
pst1
PR.Partial Int
n s
pst1 -> do
Bool -> m () -> m ()
forall a. (?callStack::CallStack) => Bool -> a -> a
assert
(Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= [Int] -> Int
forall a. Num a => [a] -> a
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
sum ((Array a -> Int) -> [Array a] -> [Int]
forall a b. (a -> b) -> [a] -> [b]
map Array a -> Int
forall a. Unbox a => Array a -> Int
Array.length (Array a
xArray a -> [Array a] -> [Array a]
forall a. a -> [a] -> [a]
:List (Array a) -> [Array a]
forall a. List a -> [a]
getList List (Array a)
backBuf)))
(() -> m ()
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return ())
let src0 :: [Array a]
src0 = Int -> [Array a] -> [Array a]
forall a. Unbox a => Int -> [Array a] -> [Array a]
takeArrayListRev Int
n (Array a
xArray a -> [Array a] -> [Array a]
forall a. a -> [a] -> [a]
:List (Array a) -> [Array a]
forall a. List a -> [a]
getList List (Array a)
backBuf)
src :: [Array a]
src = [Array a] -> [Array a]
forall a. [a] -> [a]
Prelude.reverse [Array a]
src0 [Array a] -> [Array a] -> [Array a]
forall a. [a] -> [a] -> [a]
++ [Array a]
xs
SPEC
-> [Array a]
-> List (Array a)
-> s
-> m (Either ParseError b, Stream m (Array a))
goExtract SPEC
SPEC [Array a]
src ([Array a] -> List (Array a)
forall a. [a] -> List a
List []) s
pst1
PR.Continue Int
0 s
pst1 ->
SPEC
-> [Array a]
-> List (Array a)
-> s
-> m (Either ParseError b, Stream m (Array a))
goExtract SPEC
SPEC [Array a]
xs ([Array a] -> List (Array a)
forall a. [a] -> List a
List (Array a
xArray a -> [Array a] -> [Array a]
forall a. a -> [a] -> [a]
:List (Array a) -> [Array a]
forall a. List a -> [a]
getList List (Array a)
backBuf)) s
pst1
PR.Continue Int
n s
pst1 -> do
Bool -> m () -> m ()
forall a. (?callStack::CallStack) => Bool -> a -> a
assert
(Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= [Int] -> Int
forall a. Num a => [a] -> a
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
sum ((Array a -> Int) -> [Array a] -> [Int]
forall a b. (a -> b) -> [a] -> [b]
map Array a -> Int
forall a. Unbox a => Array a -> Int
Array.length (Array a
xArray a -> [Array a] -> [Array a]
forall a. a -> [a] -> [a]
:List (Array a) -> [Array a]
forall a. List a -> [a]
getList List (Array a)
backBuf)))
(() -> m ()
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return ())
let ([Array a]
src0, [Array a]
buf1) = Int -> [Array a] -> ([Array a], [Array a])
forall a. Unbox a => Int -> [Array a] -> ([Array a], [Array a])
splitAtArrayListRev Int
n (Array a
xArray a -> [Array a] -> [Array a]
forall a. a -> [a] -> [a]
:List (Array a) -> [Array a]
forall a. List a -> [a]
getList List (Array a)
backBuf)
src :: [Array a]
src = [Array a] -> [Array a]
forall a. [a] -> [a]
Prelude.reverse [Array a]
src0 [Array a] -> [Array a] -> [Array a]
forall a. [a] -> [a] -> [a]
++ [Array a]
xs
SPEC
-> [Array a]
-> List (Array a)
-> s
-> m (Either ParseError b, Stream m (Array a))
goExtract SPEC
SPEC [Array a]
src ([Array a] -> List (Array a)
forall a. [a] -> List a
List [Array a]
buf1) s
pst1
PR.Done Int
0 b
b ->
(Either ParseError b, Stream m (Array a))
-> m (Either ParseError b, Stream m (Array a))
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (b -> Either ParseError b
forall a b. b -> Either a b
Right b
b, [Array a] -> Stream m (Array a)
forall (m :: * -> *) a. Applicative m => [a] -> Stream m a
D.fromList [Array a]
xs)
PR.Done Int
n b
b -> do
Bool -> m () -> m ()
forall a. (?callStack::CallStack) => Bool -> a -> a
assert
(Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= [Int] -> Int
forall a. Num a => [a] -> a
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
sum ((Array a -> Int) -> [Array a] -> [Int]
forall a b. (a -> b) -> [a] -> [b]
map Array a -> Int
forall a. Unbox a => Array a -> Int
Array.length (Array a
xArray a -> [Array a] -> [Array a]
forall a. a -> [a] -> [a]
:List (Array a) -> [Array a]
forall a. List a -> [a]
getList List (Array a)
backBuf)))
(() -> m ()
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return ())
let src0 :: [Array a]
src0 = Int -> [Array a] -> [Array a]
forall a. Unbox a => Int -> [Array a] -> [Array a]
takeArrayListRev Int
n (Array a
xArray a -> [Array a] -> [Array a]
forall a. a -> [a] -> [a]
:List (Array a) -> [Array a]
forall a. List a -> [a]
getList List (Array a)
backBuf)
src :: [Array a]
src = [Array a] -> [Array a]
forall a. [a] -> [a]
Prelude.reverse [Array a]
src0 [Array a] -> [Array a] -> [Array a]
forall a. [a] -> [a] -> [a]
++ [Array a]
xs
(Either ParseError b, Stream m (Array a))
-> m (Either ParseError b, Stream m (Array a))
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (b -> Either ParseError b
forall a b. b -> Either a b
Right b
b, [Array a] -> Stream m (Array a)
forall (m :: * -> *) a. Applicative m => [a] -> Stream m a
D.fromList [Array a]
src)
PR.Error String
err -> do
let src0 :: [Array a]
src0 = List (Array a) -> [Array a]
forall a. List a -> [a]
getList List (Array a)
backBuf
src :: [Array a]
src = [Array a] -> [Array a]
forall a. [a] -> [a]
Prelude.reverse [Array a]
src0 [Array a] -> [Array a] -> [Array a]
forall a. [a] -> [a] -> [a]
++ Array a
xArray a -> [Array a] -> [Array a]
forall a. a -> [a] -> [a]
:[Array a]
xs
(Either ParseError b, Stream m (Array a))
-> m (Either ParseError b, Stream m (Array a))
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (ParseError -> Either ParseError b
forall a b. a -> Either a b
Left (String -> ParseError
ParseError String
err), [Array a] -> Stream m (Array a)
forall (m :: * -> *) a. Applicative m => [a] -> Stream m a
D.fromList [Array a]
src)
{-# INLINE goStop #-}
goStop :: List (Array a) -> s -> m (Either ParseError b, Stream m (Array a))
goStop List (Array a)
backBuf s
pst = do
Step s b
pRes <- s -> m (Step s b)
extract s
pst
case Step s b
pRes of
PR.Partial Int
_ s
_ -> String -> m (Either ParseError b, Stream m (Array a))
forall a. (?callStack::CallStack) => String -> a
error String
"Bug: runArrayParserDBreak: Partial in extract"
PR.Continue Int
0 s
pst1 ->
List (Array a) -> s -> m (Either ParseError b, Stream m (Array a))
goStop List (Array a)
backBuf s
pst1
PR.Continue Int
n s
pst1 -> do
Bool -> m () -> m ()
forall a. (?callStack::CallStack) => Bool -> a -> a
assert
(Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= [Int] -> Int
forall a. Num a => [a] -> a
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
sum ((Array a -> Int) -> [Array a] -> [Int]
forall a b. (a -> b) -> [a] -> [b]
map Array a -> Int
forall a. Unbox a => Array a -> Int
Array.length (List (Array a) -> [Array a]
forall a. List a -> [a]
getList List (Array a)
backBuf)))
(() -> m ()
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return ())
let ([Array a]
src0, [Array a]
buf1) = Int -> [Array a] -> ([Array a], [Array a])
forall a. Unbox a => Int -> [Array a] -> ([Array a], [Array a])
splitAtArrayListRev Int
n (List (Array a) -> [Array a]
forall a. List a -> [a]
getList List (Array a)
backBuf)
src :: [Array a]
src = [Array a] -> [Array a]
forall a. [a] -> [a]
Prelude.reverse [Array a]
src0
SPEC
-> [Array a]
-> List (Array a)
-> s
-> m (Either ParseError b, Stream m (Array a))
goExtract SPEC
SPEC [Array a]
src ([Array a] -> List (Array a)
forall a. [a] -> List a
List [Array a]
buf1) s
pst1
PR.Done Int
0 b
b -> (Either ParseError b, Stream m (Array a))
-> m (Either ParseError b, Stream m (Array a))
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (b -> Either ParseError b
forall a b. b -> Either a b
Right b
b, Stream m (Array a)
forall (m :: * -> *) a. Applicative m => Stream m a
D.nil)
PR.Done Int
n b
b -> do
Bool -> m () -> m ()
forall a. (?callStack::CallStack) => Bool -> a -> a
assert
(Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= [Int] -> Int
forall a. Num a => [a] -> a
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
sum ((Array a -> Int) -> [Array a] -> [Int]
forall a b. (a -> b) -> [a] -> [b]
map Array a -> Int
forall a. Unbox a => Array a -> Int
Array.length (List (Array a) -> [Array a]
forall a. List a -> [a]
getList List (Array a)
backBuf)))
(() -> m ()
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return ())
let src0 :: [Array a]
src0 = Int -> [Array a] -> [Array a]
forall a. Unbox a => Int -> [Array a] -> [Array a]
takeArrayListRev Int
n (List (Array a) -> [Array a]
forall a. List a -> [a]
getList List (Array a)
backBuf)
src :: [Array a]
src = [Array a] -> [Array a]
forall a. [a] -> [a]
Prelude.reverse [Array a]
src0
(Either ParseError b, Stream m (Array a))
-> m (Either ParseError b, Stream m (Array a))
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (b -> Either ParseError b
forall a b. b -> Either a b
Right b
b, [Array a] -> Stream m (Array a)
forall (m :: * -> *) a. Applicative m => [a] -> Stream m a
D.fromList [Array a]
src)
PR.Error String
err -> do
let src0 :: [Array a]
src0 = List (Array a) -> [Array a]
forall a. List a -> [a]
getList List (Array a)
backBuf
src :: [Array a]
src = [Array a] -> [Array a]
forall a. [a] -> [a]
Prelude.reverse [Array a]
src0
(Either ParseError b, Stream m (Array a))
-> m (Either ParseError b, Stream m (Array a))
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (ParseError -> Either ParseError b
forall a b. a -> Either a b
Left (String -> ParseError
ParseError String
err), [Array a] -> Stream m (Array a)
forall (m :: * -> *) a. Applicative m => [a] -> Stream m a
D.fromList [Array a]
src)
{-# INLINE runArrayFold #-}
runArrayFold :: (MonadIO m, Unbox a) =>
ChunkFold m a b -> StreamK m (A.Array a) -> m (Either ParseError b)
runArrayFold :: forall (m :: * -> *) a b.
(MonadIO m, Unbox a) =>
ChunkFold m a b -> StreamK m (Array a) -> m (Either ParseError b)
runArrayFold (ChunkFold Parser (Array a) m b
p) StreamK m (Array a)
s = (Either ParseError b, Stream m (Array a)) -> Either ParseError b
forall a b. (a, b) -> a
fst ((Either ParseError b, Stream m (Array a)) -> Either ParseError b)
-> m (Either ParseError b, Stream m (Array a))
-> m (Either ParseError b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser (Array a) m b
-> Stream m (Array a)
-> m (Either ParseError b, Stream m (Array a))
forall (m :: * -> *) a b.
(MonadIO m, Unbox a) =>
Parser (Array a) m b
-> Stream m (Array a)
-> m (Either ParseError b, Stream m (Array a))
runArrayParserDBreak Parser (Array a) m b
p (StreamK m (Array a) -> Stream m (Array a)
forall (m :: * -> *) a. Applicative m => StreamK m a -> Stream m a
toStream StreamK m (Array a)
s)
{-# INLINE runArrayFoldBreak #-}
runArrayFoldBreak :: (MonadIO m, Unbox a) =>
ChunkFold m a b -> StreamK m (A.Array a) -> m (Either ParseError b, StreamK m (A.Array a))
runArrayFoldBreak :: forall (m :: * -> *) a b.
(MonadIO m, Unbox a) =>
ChunkFold m a b
-> StreamK m (Array a)
-> m (Either ParseError b, StreamK m (Array a))
runArrayFoldBreak (ChunkFold Parser (Array a) m b
p) StreamK m (Array a)
s =
(Stream m (Array a) -> StreamK m (Array a))
-> (Either ParseError b, Stream m (Array a))
-> (Either ParseError b, StreamK m (Array a))
forall b c a. (b -> c) -> (a, b) -> (a, c)
forall (p :: * -> * -> *) b c a.
Bifunctor p =>
(b -> c) -> p a b -> p a c
second Stream m (Array a) -> StreamK m (Array a)
forall (m :: * -> *) a. Monad m => Stream m a -> StreamK m a
fromStream ((Either ParseError b, Stream m (Array a))
-> (Either ParseError b, StreamK m (Array a)))
-> m (Either ParseError b, Stream m (Array a))
-> m (Either ParseError b, StreamK m (Array a))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser (Array a) m b
-> Stream m (Array a)
-> m (Either ParseError b, Stream m (Array a))
forall (m :: * -> *) a b.
(MonadIO m, Unbox a) =>
Parser (Array a) m b
-> Stream m (Array a)
-> m (Either ParseError b, Stream m (Array a))
runArrayParserDBreak Parser (Array a) m b
p (StreamK m (Array a) -> Stream m (Array a)
forall (m :: * -> *) a. Applicative m => StreamK m a -> Stream m a
toStream StreamK m (Array a)
s)
{-# ANN type ParseChunksState Fuse #-}
data ParseChunksState x inpBuf st pst =
ParseChunksInit inpBuf st
| ParseChunksInitBuf inpBuf
| ParseChunksInitLeftOver inpBuf
| ParseChunksStream st inpBuf !pst
| ParseChunksStop inpBuf !pst
| ParseChunksBuf inpBuf st inpBuf !pst
| inpBuf inpBuf !pst
| ParseChunksYield x (ParseChunksState x inpBuf st pst)
{-# INLINE_NORMAL runArrayFoldManyD #-}
runArrayFoldManyD
:: (Monad m, Unbox a)
=> ChunkFold m a b
-> D.Stream m (Array a)
-> D.Stream m (Either ParseError b)
runArrayFoldManyD :: forall (m :: * -> *) a b.
(Monad m, Unbox a) =>
ChunkFold m a b
-> Stream m (Array a) -> Stream m (Either ParseError b)
runArrayFoldManyD
(ChunkFold (PRD.Parser s -> Array a -> m (Step s b)
pstep m (Initial s b)
initial s -> m (Step s b)
extract)) (D.Stream State StreamK m (Array a) -> s -> m (Step s (Array a))
step s
state) =
(State StreamK m (Either ParseError b)
-> ParseChunksState (Either ParseError b) [Array a] s s
-> m (Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)))
-> ParseChunksState (Either ParseError b) [Array a] s s
-> Stream m (Either ParseError b)
forall (m :: * -> *) a s.
(State StreamK m a -> s -> m (Step s a)) -> s -> Stream m a
D.Stream State StreamK m (Either ParseError b)
-> ParseChunksState (Either ParseError b) [Array a] s s
-> m (Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b))
forall {m :: * -> *} {a}.
State StreamK m a
-> ParseChunksState (Either ParseError b) [Array a] s s
-> m (Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b))
stepOuter ([Array a]
-> s -> ParseChunksState (Either ParseError b) [Array a] s s
forall x inpBuf st pst.
inpBuf -> st -> ParseChunksState x inpBuf st pst
ParseChunksInit [] s
state)
where
{-# INLINE_LATE stepOuter #-}
stepOuter :: State StreamK m a
-> ParseChunksState (Either ParseError b) [Array a] s s
-> m (Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b))
stepOuter State StreamK m a
gst (ParseChunksInit [] s
st) = do
Step s (Array a)
r <- State StreamK m (Array a) -> s -> m (Step s (Array a))
step (State StreamK m a -> State StreamK m (Array a)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a (n :: * -> *) b.
State t m a -> State t n b
adaptState State StreamK m a
gst) s
st
case Step s (Array a)
r of
D.Yield Array a
x s
s -> do
Initial s b
res <- m (Initial s b)
initial
case Initial s b
res of
PRD.IPartial s
ps ->
Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
-> m (Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b))
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
-> m (Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)))
-> Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
-> m (Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b))
forall a b. (a -> b) -> a -> b
$ ParseChunksState (Either ParseError b) [Array a] s s
-> Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
forall s a. s -> Step s a
D.Skip (ParseChunksState (Either ParseError b) [Array a] s s
-> Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b))
-> ParseChunksState (Either ParseError b) [Array a] s s
-> Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
forall a b. (a -> b) -> a -> b
$ [Array a]
-> s
-> [Array a]
-> s
-> ParseChunksState (Either ParseError b) [Array a] s s
forall x inpBuf st pst.
inpBuf -> st -> inpBuf -> pst -> ParseChunksState x inpBuf st pst
ParseChunksBuf [Array a
x] s
s [] s
ps
PRD.IDone b
pb -> do
let next :: ParseChunksState x [Array a] s pst
next = [Array a] -> s -> ParseChunksState x [Array a] s pst
forall x inpBuf st pst.
inpBuf -> st -> ParseChunksState x inpBuf st pst
ParseChunksInit [Array a
x] s
s
Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
-> m (Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b))
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
-> m (Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)))
-> Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
-> m (Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b))
forall a b. (a -> b) -> a -> b
$ ParseChunksState (Either ParseError b) [Array a] s s
-> Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
forall s a. s -> Step s a
D.Skip (ParseChunksState (Either ParseError b) [Array a] s s
-> Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b))
-> ParseChunksState (Either ParseError b) [Array a] s s
-> Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
forall a b. (a -> b) -> a -> b
$ Either ParseError b
-> ParseChunksState (Either ParseError b) [Array a] s s
-> ParseChunksState (Either ParseError b) [Array a] s s
forall x inpBuf st pst.
x
-> ParseChunksState x inpBuf st pst
-> ParseChunksState x inpBuf st pst
ParseChunksYield (b -> Either ParseError b
forall a b. b -> Either a b
Right b
pb) ParseChunksState (Either ParseError b) [Array a] s s
forall {x} {pst}. ParseChunksState x [Array a] s pst
next
PRD.IError String
err -> do
let next :: ParseChunksState x [a] st pst
next = [a] -> ParseChunksState x [a] st pst
forall x inpBuf st pst. inpBuf -> ParseChunksState x inpBuf st pst
ParseChunksInitLeftOver []
Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
-> m (Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b))
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return
(Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
-> m (Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)))
-> Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
-> m (Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b))
forall a b. (a -> b) -> a -> b
$ ParseChunksState (Either ParseError b) [Array a] s s
-> Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
forall s a. s -> Step s a
D.Skip
(ParseChunksState (Either ParseError b) [Array a] s s
-> Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b))
-> ParseChunksState (Either ParseError b) [Array a] s s
-> Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
forall a b. (a -> b) -> a -> b
$ Either ParseError b
-> ParseChunksState (Either ParseError b) [Array a] s s
-> ParseChunksState (Either ParseError b) [Array a] s s
forall x inpBuf st pst.
x
-> ParseChunksState x inpBuf st pst
-> ParseChunksState x inpBuf st pst
ParseChunksYield (ParseError -> Either ParseError b
forall a b. a -> Either a b
Left (String -> ParseError
ParseError String
err)) ParseChunksState (Either ParseError b) [Array a] s s
forall {x} {a} {st} {pst}. ParseChunksState x [a] st pst
next
D.Skip s
s -> Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
-> m (Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b))
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
-> m (Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)))
-> Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
-> m (Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b))
forall a b. (a -> b) -> a -> b
$ ParseChunksState (Either ParseError b) [Array a] s s
-> Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
forall s a. s -> Step s a
D.Skip (ParseChunksState (Either ParseError b) [Array a] s s
-> Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b))
-> ParseChunksState (Either ParseError b) [Array a] s s
-> Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
forall a b. (a -> b) -> a -> b
$ [Array a]
-> s -> ParseChunksState (Either ParseError b) [Array a] s s
forall x inpBuf st pst.
inpBuf -> st -> ParseChunksState x inpBuf st pst
ParseChunksInit [] s
s
Step s (Array a)
D.Stop -> Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
-> m (Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b))
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
forall s a. Step s a
D.Stop
stepOuter State StreamK m a
_ (ParseChunksInit [Array a]
src s
st) = do
Initial s b
res <- m (Initial s b)
initial
case Initial s b
res of
PRD.IPartial s
ps ->
Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
-> m (Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b))
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
-> m (Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)))
-> Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
-> m (Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b))
forall a b. (a -> b) -> a -> b
$ ParseChunksState (Either ParseError b) [Array a] s s
-> Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
forall s a. s -> Step s a
D.Skip (ParseChunksState (Either ParseError b) [Array a] s s
-> Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b))
-> ParseChunksState (Either ParseError b) [Array a] s s
-> Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
forall a b. (a -> b) -> a -> b
$ [Array a]
-> s
-> [Array a]
-> s
-> ParseChunksState (Either ParseError b) [Array a] s s
forall x inpBuf st pst.
inpBuf -> st -> inpBuf -> pst -> ParseChunksState x inpBuf st pst
ParseChunksBuf [Array a]
src s
st [] s
ps
PRD.IDone b
pb ->
let next :: ParseChunksState x [Array a] s pst
next = [Array a] -> s -> ParseChunksState x [Array a] s pst
forall x inpBuf st pst.
inpBuf -> st -> ParseChunksState x inpBuf st pst
ParseChunksInit [Array a]
src s
st
in Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
-> m (Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b))
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
-> m (Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)))
-> Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
-> m (Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b))
forall a b. (a -> b) -> a -> b
$ ParseChunksState (Either ParseError b) [Array a] s s
-> Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
forall s a. s -> Step s a
D.Skip (ParseChunksState (Either ParseError b) [Array a] s s
-> Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b))
-> ParseChunksState (Either ParseError b) [Array a] s s
-> Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
forall a b. (a -> b) -> a -> b
$ Either ParseError b
-> ParseChunksState (Either ParseError b) [Array a] s s
-> ParseChunksState (Either ParseError b) [Array a] s s
forall x inpBuf st pst.
x
-> ParseChunksState x inpBuf st pst
-> ParseChunksState x inpBuf st pst
ParseChunksYield (b -> Either ParseError b
forall a b. b -> Either a b
Right b
pb) ParseChunksState (Either ParseError b) [Array a] s s
forall {x} {pst}. ParseChunksState x [Array a] s pst
next
PRD.IError String
err -> do
let next :: ParseChunksState x [a] st pst
next = [a] -> ParseChunksState x [a] st pst
forall x inpBuf st pst. inpBuf -> ParseChunksState x inpBuf st pst
ParseChunksInitLeftOver []
Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
-> m (Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b))
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return
(Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
-> m (Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)))
-> Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
-> m (Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b))
forall a b. (a -> b) -> a -> b
$ ParseChunksState (Either ParseError b) [Array a] s s
-> Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
forall s a. s -> Step s a
D.Skip
(ParseChunksState (Either ParseError b) [Array a] s s
-> Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b))
-> ParseChunksState (Either ParseError b) [Array a] s s
-> Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
forall a b. (a -> b) -> a -> b
$ Either ParseError b
-> ParseChunksState (Either ParseError b) [Array a] s s
-> ParseChunksState (Either ParseError b) [Array a] s s
forall x inpBuf st pst.
x
-> ParseChunksState x inpBuf st pst
-> ParseChunksState x inpBuf st pst
ParseChunksYield (ParseError -> Either ParseError b
forall a b. a -> Either a b
Left (String -> ParseError
ParseError String
err)) ParseChunksState (Either ParseError b) [Array a] s s
forall {x} {a} {st} {pst}. ParseChunksState x [a] st pst
next
stepOuter State StreamK m a
_ (ParseChunksInitBuf [Array a]
src) = do
Initial s b
res <- m (Initial s b)
initial
case Initial s b
res of
PRD.IPartial s
ps ->
Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
-> m (Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b))
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
-> m (Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)))
-> Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
-> m (Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b))
forall a b. (a -> b) -> a -> b
$ ParseChunksState (Either ParseError b) [Array a] s s
-> Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
forall s a. s -> Step s a
D.Skip (ParseChunksState (Either ParseError b) [Array a] s s
-> Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b))
-> ParseChunksState (Either ParseError b) [Array a] s s
-> Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
forall a b. (a -> b) -> a -> b
$ [Array a]
-> [Array a]
-> s
-> ParseChunksState (Either ParseError b) [Array a] s s
forall x inpBuf st pst.
inpBuf -> inpBuf -> pst -> ParseChunksState x inpBuf st pst
ParseChunksExtract [Array a]
src [] s
ps
PRD.IDone b
pb ->
let next :: ParseChunksState x [Array a] st pst
next = [Array a] -> ParseChunksState x [Array a] st pst
forall x inpBuf st pst. inpBuf -> ParseChunksState x inpBuf st pst
ParseChunksInitBuf [Array a]
src
in Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
-> m (Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b))
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
-> m (Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)))
-> Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
-> m (Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b))
forall a b. (a -> b) -> a -> b
$ ParseChunksState (Either ParseError b) [Array a] s s
-> Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
forall s a. s -> Step s a
D.Skip (ParseChunksState (Either ParseError b) [Array a] s s
-> Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b))
-> ParseChunksState (Either ParseError b) [Array a] s s
-> Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
forall a b. (a -> b) -> a -> b
$ Either ParseError b
-> ParseChunksState (Either ParseError b) [Array a] s s
-> ParseChunksState (Either ParseError b) [Array a] s s
forall x inpBuf st pst.
x
-> ParseChunksState x inpBuf st pst
-> ParseChunksState x inpBuf st pst
ParseChunksYield (b -> Either ParseError b
forall a b. b -> Either a b
Right b
pb) ParseChunksState (Either ParseError b) [Array a] s s
forall {x} {st} {pst}. ParseChunksState x [Array a] st pst
next
PRD.IError String
err -> do
let next :: ParseChunksState x [a] st pst
next = [a] -> ParseChunksState x [a] st pst
forall x inpBuf st pst. inpBuf -> ParseChunksState x inpBuf st pst
ParseChunksInitLeftOver []
Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
-> m (Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b))
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return
(Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
-> m (Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)))
-> Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
-> m (Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b))
forall a b. (a -> b) -> a -> b
$ ParseChunksState (Either ParseError b) [Array a] s s
-> Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
forall s a. s -> Step s a
D.Skip
(ParseChunksState (Either ParseError b) [Array a] s s
-> Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b))
-> ParseChunksState (Either ParseError b) [Array a] s s
-> Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
forall a b. (a -> b) -> a -> b
$ Either ParseError b
-> ParseChunksState (Either ParseError b) [Array a] s s
-> ParseChunksState (Either ParseError b) [Array a] s s
forall x inpBuf st pst.
x
-> ParseChunksState x inpBuf st pst
-> ParseChunksState x inpBuf st pst
ParseChunksYield (ParseError -> Either ParseError b
forall a b. a -> Either a b
Left (String -> ParseError
ParseError String
err)) ParseChunksState (Either ParseError b) [Array a] s s
forall {x} {a} {st} {pst}. ParseChunksState x [a] st pst
next
stepOuter State StreamK m a
_ (ParseChunksInitLeftOver [Array a]
_) = Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
-> m (Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b))
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
forall s a. Step s a
D.Stop
stepOuter State StreamK m a
gst (ParseChunksStream s
st [Array a]
backBuf s
pst) = do
Step s (Array a)
r <- State StreamK m (Array a) -> s -> m (Step s (Array a))
step (State StreamK m a -> State StreamK m (Array a)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a (n :: * -> *) b.
State t m a -> State t n b
adaptState State StreamK m a
gst) s
st
case Step s (Array a)
r of
D.Yield Array a
x s
s -> do
Step s b
pRes <- s -> Array a -> m (Step s b)
pstep s
pst Array a
x
case Step s b
pRes of
PR.Partial Int
0 s
pst1 ->
Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
-> m (Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b))
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
-> m (Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)))
-> Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
-> m (Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b))
forall a b. (a -> b) -> a -> b
$ ParseChunksState (Either ParseError b) [Array a] s s
-> Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
forall s a. s -> Step s a
D.Skip (ParseChunksState (Either ParseError b) [Array a] s s
-> Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b))
-> ParseChunksState (Either ParseError b) [Array a] s s
-> Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
forall a b. (a -> b) -> a -> b
$ s
-> [Array a]
-> s
-> ParseChunksState (Either ParseError b) [Array a] s s
forall x inpBuf st pst.
st -> inpBuf -> pst -> ParseChunksState x inpBuf st pst
ParseChunksStream s
s [] s
pst1
PR.Partial Int
n s
pst1 -> do
Bool -> m () -> m ()
forall a. (?callStack::CallStack) => Bool -> a -> a
assert
(Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= [Int] -> Int
forall a. Num a => [a] -> a
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
sum ((Array a -> Int) -> [Array a] -> [Int]
forall a b. (a -> b) -> [a] -> [b]
map Array a -> Int
forall a. Unbox a => Array a -> Int
Array.length (Array a
xArray a -> [Array a] -> [Array a]
forall a. a -> [a] -> [a]
:[Array a]
backBuf)))
(() -> m ()
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return ())
let src0 :: [Array a]
src0 = Int -> [Array a] -> [Array a]
forall a. Unbox a => Int -> [Array a] -> [Array a]
takeArrayListRev Int
n (Array a
xArray a -> [Array a] -> [Array a]
forall a. a -> [a] -> [a]
:[Array a]
backBuf)
src :: [Array a]
src = [Array a] -> [Array a]
forall a. [a] -> [a]
Prelude.reverse [Array a]
src0
Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
-> m (Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b))
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
-> m (Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)))
-> Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
-> m (Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b))
forall a b. (a -> b) -> a -> b
$ ParseChunksState (Either ParseError b) [Array a] s s
-> Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
forall s a. s -> Step s a
D.Skip (ParseChunksState (Either ParseError b) [Array a] s s
-> Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b))
-> ParseChunksState (Either ParseError b) [Array a] s s
-> Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
forall a b. (a -> b) -> a -> b
$ [Array a]
-> s
-> [Array a]
-> s
-> ParseChunksState (Either ParseError b) [Array a] s s
forall x inpBuf st pst.
inpBuf -> st -> inpBuf -> pst -> ParseChunksState x inpBuf st pst
ParseChunksBuf [Array a]
src s
s [] s
pst1
PR.Continue Int
0 s
pst1 ->
Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
-> m (Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b))
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
-> m (Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)))
-> Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
-> m (Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b))
forall a b. (a -> b) -> a -> b
$ ParseChunksState (Either ParseError b) [Array a] s s
-> Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
forall s a. s -> Step s a
D.Skip (ParseChunksState (Either ParseError b) [Array a] s s
-> Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b))
-> ParseChunksState (Either ParseError b) [Array a] s s
-> Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
forall a b. (a -> b) -> a -> b
$ s
-> [Array a]
-> s
-> ParseChunksState (Either ParseError b) [Array a] s s
forall x inpBuf st pst.
st -> inpBuf -> pst -> ParseChunksState x inpBuf st pst
ParseChunksStream s
s (Array a
xArray a -> [Array a] -> [Array a]
forall a. a -> [a] -> [a]
:[Array a]
backBuf) s
pst1
PR.Continue Int
n s
pst1 -> do
Bool -> m () -> m ()
forall a. (?callStack::CallStack) => Bool -> a -> a
assert
(Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= [Int] -> Int
forall a. Num a => [a] -> a
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
sum ((Array a -> Int) -> [Array a] -> [Int]
forall a b. (a -> b) -> [a] -> [b]
map Array a -> Int
forall a. Unbox a => Array a -> Int
Array.length (Array a
xArray a -> [Array a] -> [Array a]
forall a. a -> [a] -> [a]
:[Array a]
backBuf)))
(() -> m ()
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return ())
let ([Array a]
src0, [Array a]
buf1) = Int -> [Array a] -> ([Array a], [Array a])
forall a. Unbox a => Int -> [Array a] -> ([Array a], [Array a])
splitAtArrayListRev Int
n (Array a
xArray a -> [Array a] -> [Array a]
forall a. a -> [a] -> [a]
:[Array a]
backBuf)
src :: [Array a]
src = [Array a] -> [Array a]
forall a. [a] -> [a]
Prelude.reverse [Array a]
src0
Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
-> m (Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b))
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
-> m (Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)))
-> Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
-> m (Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b))
forall a b. (a -> b) -> a -> b
$ ParseChunksState (Either ParseError b) [Array a] s s
-> Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
forall s a. s -> Step s a
D.Skip (ParseChunksState (Either ParseError b) [Array a] s s
-> Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b))
-> ParseChunksState (Either ParseError b) [Array a] s s
-> Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
forall a b. (a -> b) -> a -> b
$ [Array a]
-> s
-> [Array a]
-> s
-> ParseChunksState (Either ParseError b) [Array a] s s
forall x inpBuf st pst.
inpBuf -> st -> inpBuf -> pst -> ParseChunksState x inpBuf st pst
ParseChunksBuf [Array a]
src s
s [Array a]
buf1 s
pst1
PR.Done Int
0 b
b -> do
Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
-> m (Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b))
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
-> m (Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)))
-> Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
-> m (Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b))
forall a b. (a -> b) -> a -> b
$ ParseChunksState (Either ParseError b) [Array a] s s
-> Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
forall s a. s -> Step s a
D.Skip (ParseChunksState (Either ParseError b) [Array a] s s
-> Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b))
-> ParseChunksState (Either ParseError b) [Array a] s s
-> Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
forall a b. (a -> b) -> a -> b
$
Either ParseError b
-> ParseChunksState (Either ParseError b) [Array a] s s
-> ParseChunksState (Either ParseError b) [Array a] s s
forall x inpBuf st pst.
x
-> ParseChunksState x inpBuf st pst
-> ParseChunksState x inpBuf st pst
ParseChunksYield (b -> Either ParseError b
forall a b. b -> Either a b
Right b
b) ([Array a]
-> s -> ParseChunksState (Either ParseError b) [Array a] s s
forall x inpBuf st pst.
inpBuf -> st -> ParseChunksState x inpBuf st pst
ParseChunksInit [] s
s)
PR.Done Int
n b
b -> do
Bool -> m () -> m ()
forall a. (?callStack::CallStack) => Bool -> a -> a
assert
(Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= [Int] -> Int
forall a. Num a => [a] -> a
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
sum ((Array a -> Int) -> [Array a] -> [Int]
forall a b. (a -> b) -> [a] -> [b]
map Array a -> Int
forall a. Unbox a => Array a -> Int
Array.length (Array a
xArray a -> [Array a] -> [Array a]
forall a. a -> [a] -> [a]
:[Array a]
backBuf)))
(() -> m ()
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return ())
let src0 :: [Array a]
src0 = Int -> [Array a] -> [Array a]
forall a. Unbox a => Int -> [Array a] -> [Array a]
takeArrayListRev Int
n (Array a
xArray a -> [Array a] -> [Array a]
forall a. a -> [a] -> [a]
:[Array a]
backBuf)
src :: [Array a]
src = [Array a] -> [Array a]
forall a. [a] -> [a]
Prelude.reverse [Array a]
src0
next :: ParseChunksState x [Array a] s pst
next = [Array a] -> s -> ParseChunksState x [Array a] s pst
forall x inpBuf st pst.
inpBuf -> st -> ParseChunksState x inpBuf st pst
ParseChunksInit [Array a]
src s
s
Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
-> m (Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b))
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return
(Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
-> m (Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)))
-> Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
-> m (Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b))
forall a b. (a -> b) -> a -> b
$ ParseChunksState (Either ParseError b) [Array a] s s
-> Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
forall s a. s -> Step s a
D.Skip
(ParseChunksState (Either ParseError b) [Array a] s s
-> Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b))
-> ParseChunksState (Either ParseError b) [Array a] s s
-> Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
forall a b. (a -> b) -> a -> b
$ Either ParseError b
-> ParseChunksState (Either ParseError b) [Array a] s s
-> ParseChunksState (Either ParseError b) [Array a] s s
forall x inpBuf st pst.
x
-> ParseChunksState x inpBuf st pst
-> ParseChunksState x inpBuf st pst
ParseChunksYield (b -> Either ParseError b
forall a b. b -> Either a b
Right b
b) ParseChunksState (Either ParseError b) [Array a] s s
forall {x} {pst}. ParseChunksState x [Array a] s pst
next
PR.Error String
err -> do
let next :: ParseChunksState x [a] st pst
next = [a] -> ParseChunksState x [a] st pst
forall x inpBuf st pst. inpBuf -> ParseChunksState x inpBuf st pst
ParseChunksInitLeftOver []
Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
-> m (Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b))
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return
(Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
-> m (Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)))
-> Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
-> m (Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b))
forall a b. (a -> b) -> a -> b
$ ParseChunksState (Either ParseError b) [Array a] s s
-> Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
forall s a. s -> Step s a
D.Skip
(ParseChunksState (Either ParseError b) [Array a] s s
-> Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b))
-> ParseChunksState (Either ParseError b) [Array a] s s
-> Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
forall a b. (a -> b) -> a -> b
$ Either ParseError b
-> ParseChunksState (Either ParseError b) [Array a] s s
-> ParseChunksState (Either ParseError b) [Array a] s s
forall x inpBuf st pst.
x
-> ParseChunksState x inpBuf st pst
-> ParseChunksState x inpBuf st pst
ParseChunksYield (ParseError -> Either ParseError b
forall a b. a -> Either a b
Left (String -> ParseError
ParseError String
err)) ParseChunksState (Either ParseError b) [Array a] s s
forall {x} {a} {st} {pst}. ParseChunksState x [a] st pst
next
D.Skip s
s -> Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
-> m (Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b))
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
-> m (Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)))
-> Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
-> m (Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b))
forall a b. (a -> b) -> a -> b
$ ParseChunksState (Either ParseError b) [Array a] s s
-> Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
forall s a. s -> Step s a
D.Skip (ParseChunksState (Either ParseError b) [Array a] s s
-> Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b))
-> ParseChunksState (Either ParseError b) [Array a] s s
-> Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
forall a b. (a -> b) -> a -> b
$ s
-> [Array a]
-> s
-> ParseChunksState (Either ParseError b) [Array a] s s
forall x inpBuf st pst.
st -> inpBuf -> pst -> ParseChunksState x inpBuf st pst
ParseChunksStream s
s [Array a]
backBuf s
pst
Step s (Array a)
D.Stop -> Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
-> m (Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b))
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
-> m (Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)))
-> Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
-> m (Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b))
forall a b. (a -> b) -> a -> b
$ ParseChunksState (Either ParseError b) [Array a] s s
-> Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
forall s a. s -> Step s a
D.Skip (ParseChunksState (Either ParseError b) [Array a] s s
-> Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b))
-> ParseChunksState (Either ParseError b) [Array a] s s
-> Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
forall a b. (a -> b) -> a -> b
$ [Array a]
-> s -> ParseChunksState (Either ParseError b) [Array a] s s
forall x inpBuf st pst.
inpBuf -> pst -> ParseChunksState x inpBuf st pst
ParseChunksStop [Array a]
backBuf s
pst
stepOuter State StreamK m a
_ (ParseChunksBuf [] s
s [Array a]
buf s
pst) =
Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
-> m (Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b))
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
-> m (Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)))
-> Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
-> m (Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b))
forall a b. (a -> b) -> a -> b
$ ParseChunksState (Either ParseError b) [Array a] s s
-> Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
forall s a. s -> Step s a
D.Skip (ParseChunksState (Either ParseError b) [Array a] s s
-> Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b))
-> ParseChunksState (Either ParseError b) [Array a] s s
-> Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
forall a b. (a -> b) -> a -> b
$ s
-> [Array a]
-> s
-> ParseChunksState (Either ParseError b) [Array a] s s
forall x inpBuf st pst.
st -> inpBuf -> pst -> ParseChunksState x inpBuf st pst
ParseChunksStream s
s [Array a]
buf s
pst
stepOuter State StreamK m a
_ (ParseChunksBuf (Array a
x:[Array a]
xs) s
s [Array a]
backBuf s
pst) = do
Step s b
pRes <- s -> Array a -> m (Step s b)
pstep s
pst Array a
x
case Step s b
pRes of
PR.Partial Int
0 s
pst1 ->
Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
-> m (Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b))
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
-> m (Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)))
-> Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
-> m (Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b))
forall a b. (a -> b) -> a -> b
$ ParseChunksState (Either ParseError b) [Array a] s s
-> Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
forall s a. s -> Step s a
D.Skip (ParseChunksState (Either ParseError b) [Array a] s s
-> Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b))
-> ParseChunksState (Either ParseError b) [Array a] s s
-> Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
forall a b. (a -> b) -> a -> b
$ [Array a]
-> s
-> [Array a]
-> s
-> ParseChunksState (Either ParseError b) [Array a] s s
forall x inpBuf st pst.
inpBuf -> st -> inpBuf -> pst -> ParseChunksState x inpBuf st pst
ParseChunksBuf [Array a]
xs s
s [] s
pst1
PR.Partial Int
n s
pst1 -> do
Bool -> m () -> m ()
forall a. (?callStack::CallStack) => Bool -> a -> a
assert (Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= [Int] -> Int
forall a. Num a => [a] -> a
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
sum ((Array a -> Int) -> [Array a] -> [Int]
forall a b. (a -> b) -> [a] -> [b]
map Array a -> Int
forall a. Unbox a => Array a -> Int
Array.length (Array a
xArray a -> [Array a] -> [Array a]
forall a. a -> [a] -> [a]
:[Array a]
backBuf))) (() -> m ()
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return ())
let src0 :: [Array a]
src0 = Int -> [Array a] -> [Array a]
forall a. Unbox a => Int -> [Array a] -> [Array a]
takeArrayListRev Int
n (Array a
xArray a -> [Array a] -> [Array a]
forall a. a -> [a] -> [a]
:[Array a]
backBuf)
src :: [Array a]
src = [Array a] -> [Array a]
forall a. [a] -> [a]
Prelude.reverse [Array a]
src0 [Array a] -> [Array a] -> [Array a]
forall a. [a] -> [a] -> [a]
++ [Array a]
xs
Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
-> m (Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b))
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
-> m (Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)))
-> Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
-> m (Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b))
forall a b. (a -> b) -> a -> b
$ ParseChunksState (Either ParseError b) [Array a] s s
-> Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
forall s a. s -> Step s a
D.Skip (ParseChunksState (Either ParseError b) [Array a] s s
-> Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b))
-> ParseChunksState (Either ParseError b) [Array a] s s
-> Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
forall a b. (a -> b) -> a -> b
$ [Array a]
-> s
-> [Array a]
-> s
-> ParseChunksState (Either ParseError b) [Array a] s s
forall x inpBuf st pst.
inpBuf -> st -> inpBuf -> pst -> ParseChunksState x inpBuf st pst
ParseChunksBuf [Array a]
src s
s [] s
pst1
PR.Continue Int
0 s
pst1 ->
Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
-> m (Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b))
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
-> m (Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)))
-> Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
-> m (Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b))
forall a b. (a -> b) -> a -> b
$ ParseChunksState (Either ParseError b) [Array a] s s
-> Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
forall s a. s -> Step s a
D.Skip (ParseChunksState (Either ParseError b) [Array a] s s
-> Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b))
-> ParseChunksState (Either ParseError b) [Array a] s s
-> Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
forall a b. (a -> b) -> a -> b
$ [Array a]
-> s
-> [Array a]
-> s
-> ParseChunksState (Either ParseError b) [Array a] s s
forall x inpBuf st pst.
inpBuf -> st -> inpBuf -> pst -> ParseChunksState x inpBuf st pst
ParseChunksBuf [Array a]
xs s
s (Array a
xArray a -> [Array a] -> [Array a]
forall a. a -> [a] -> [a]
:[Array a]
backBuf) s
pst1
PR.Continue Int
n s
pst1 -> do
Bool -> m () -> m ()
forall a. (?callStack::CallStack) => Bool -> a -> a
assert (Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= [Int] -> Int
forall a. Num a => [a] -> a
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
sum ((Array a -> Int) -> [Array a] -> [Int]
forall a b. (a -> b) -> [a] -> [b]
map Array a -> Int
forall a. Unbox a => Array a -> Int
Array.length (Array a
xArray a -> [Array a] -> [Array a]
forall a. a -> [a] -> [a]
:[Array a]
backBuf))) (() -> m ()
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return ())
let ([Array a]
src0, [Array a]
buf1) = Int -> [Array a] -> ([Array a], [Array a])
forall a. Unbox a => Int -> [Array a] -> ([Array a], [Array a])
splitAtArrayListRev Int
n (Array a
xArray a -> [Array a] -> [Array a]
forall a. a -> [a] -> [a]
:[Array a]
backBuf)
src :: [Array a]
src = [Array a] -> [Array a]
forall a. [a] -> [a]
Prelude.reverse [Array a]
src0 [Array a] -> [Array a] -> [Array a]
forall a. [a] -> [a] -> [a]
++ [Array a]
xs
Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
-> m (Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b))
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
-> m (Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)))
-> Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
-> m (Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b))
forall a b. (a -> b) -> a -> b
$ ParseChunksState (Either ParseError b) [Array a] s s
-> Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
forall s a. s -> Step s a
D.Skip (ParseChunksState (Either ParseError b) [Array a] s s
-> Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b))
-> ParseChunksState (Either ParseError b) [Array a] s s
-> Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
forall a b. (a -> b) -> a -> b
$ [Array a]
-> s
-> [Array a]
-> s
-> ParseChunksState (Either ParseError b) [Array a] s s
forall x inpBuf st pst.
inpBuf -> st -> inpBuf -> pst -> ParseChunksState x inpBuf st pst
ParseChunksBuf [Array a]
src s
s [Array a]
buf1 s
pst1
PR.Done Int
0 b
b ->
Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
-> m (Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b))
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return
(Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
-> m (Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)))
-> Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
-> m (Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b))
forall a b. (a -> b) -> a -> b
$ ParseChunksState (Either ParseError b) [Array a] s s
-> Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
forall s a. s -> Step s a
D.Skip
(ParseChunksState (Either ParseError b) [Array a] s s
-> Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b))
-> ParseChunksState (Either ParseError b) [Array a] s s
-> Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
forall a b. (a -> b) -> a -> b
$ Either ParseError b
-> ParseChunksState (Either ParseError b) [Array a] s s
-> ParseChunksState (Either ParseError b) [Array a] s s
forall x inpBuf st pst.
x
-> ParseChunksState x inpBuf st pst
-> ParseChunksState x inpBuf st pst
ParseChunksYield (b -> Either ParseError b
forall a b. b -> Either a b
Right b
b) ([Array a]
-> s -> ParseChunksState (Either ParseError b) [Array a] s s
forall x inpBuf st pst.
inpBuf -> st -> ParseChunksState x inpBuf st pst
ParseChunksInit [Array a]
xs s
s)
PR.Done Int
n b
b -> do
Bool -> m () -> m ()
forall a. (?callStack::CallStack) => Bool -> a -> a
assert (Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= [Int] -> Int
forall a. Num a => [a] -> a
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
sum ((Array a -> Int) -> [Array a] -> [Int]
forall a b. (a -> b) -> [a] -> [b]
map Array a -> Int
forall a. Unbox a => Array a -> Int
Array.length (Array a
xArray a -> [Array a] -> [Array a]
forall a. a -> [a] -> [a]
:[Array a]
backBuf))) (() -> m ()
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return ())
let src0 :: [Array a]
src0 = Int -> [Array a] -> [Array a]
forall a. Unbox a => Int -> [Array a] -> [Array a]
takeArrayListRev Int
n (Array a
xArray a -> [Array a] -> [Array a]
forall a. a -> [a] -> [a]
:[Array a]
backBuf)
src :: [Array a]
src = [Array a] -> [Array a]
forall a. [a] -> [a]
Prelude.reverse [Array a]
src0 [Array a] -> [Array a] -> [Array a]
forall a. [a] -> [a] -> [a]
++ [Array a]
xs
Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
-> m (Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b))
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return
(Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
-> m (Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)))
-> Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
-> m (Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b))
forall a b. (a -> b) -> a -> b
$ ParseChunksState (Either ParseError b) [Array a] s s
-> Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
forall s a. s -> Step s a
D.Skip
(ParseChunksState (Either ParseError b) [Array a] s s
-> Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b))
-> ParseChunksState (Either ParseError b) [Array a] s s
-> Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
forall a b. (a -> b) -> a -> b
$ Either ParseError b
-> ParseChunksState (Either ParseError b) [Array a] s s
-> ParseChunksState (Either ParseError b) [Array a] s s
forall x inpBuf st pst.
x
-> ParseChunksState x inpBuf st pst
-> ParseChunksState x inpBuf st pst
ParseChunksYield (b -> Either ParseError b
forall a b. b -> Either a b
Right b
b) ([Array a]
-> s -> ParseChunksState (Either ParseError b) [Array a] s s
forall x inpBuf st pst.
inpBuf -> st -> ParseChunksState x inpBuf st pst
ParseChunksInit [Array a]
src s
s)
PR.Error String
err -> do
let next :: ParseChunksState x [a] st pst
next = [a] -> ParseChunksState x [a] st pst
forall x inpBuf st pst. inpBuf -> ParseChunksState x inpBuf st pst
ParseChunksInitLeftOver []
Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
-> m (Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b))
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return
(Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
-> m (Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)))
-> Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
-> m (Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b))
forall a b. (a -> b) -> a -> b
$ ParseChunksState (Either ParseError b) [Array a] s s
-> Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
forall s a. s -> Step s a
D.Skip
(ParseChunksState (Either ParseError b) [Array a] s s
-> Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b))
-> ParseChunksState (Either ParseError b) [Array a] s s
-> Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
forall a b. (a -> b) -> a -> b
$ Either ParseError b
-> ParseChunksState (Either ParseError b) [Array a] s s
-> ParseChunksState (Either ParseError b) [Array a] s s
forall x inpBuf st pst.
x
-> ParseChunksState x inpBuf st pst
-> ParseChunksState x inpBuf st pst
ParseChunksYield (ParseError -> Either ParseError b
forall a b. a -> Either a b
Left (String -> ParseError
ParseError String
err)) ParseChunksState (Either ParseError b) [Array a] s s
forall {x} {a} {st} {pst}. ParseChunksState x [a] st pst
next
stepOuter State StreamK m a
_ (ParseChunksExtract [] [Array a]
buf s
pst) =
Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
-> m (Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b))
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
-> m (Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)))
-> Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
-> m (Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b))
forall a b. (a -> b) -> a -> b
$ ParseChunksState (Either ParseError b) [Array a] s s
-> Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
forall s a. s -> Step s a
D.Skip (ParseChunksState (Either ParseError b) [Array a] s s
-> Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b))
-> ParseChunksState (Either ParseError b) [Array a] s s
-> Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
forall a b. (a -> b) -> a -> b
$ [Array a]
-> s -> ParseChunksState (Either ParseError b) [Array a] s s
forall x inpBuf st pst.
inpBuf -> pst -> ParseChunksState x inpBuf st pst
ParseChunksStop [Array a]
buf s
pst
stepOuter State StreamK m a
_ (ParseChunksExtract (Array a
x:[Array a]
xs) [Array a]
backBuf s
pst) = do
Step s b
pRes <- s -> Array a -> m (Step s b)
pstep s
pst Array a
x
case Step s b
pRes of
PR.Partial Int
0 s
pst1 ->
Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
-> m (Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b))
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
-> m (Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)))
-> Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
-> m (Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b))
forall a b. (a -> b) -> a -> b
$ ParseChunksState (Either ParseError b) [Array a] s s
-> Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
forall s a. s -> Step s a
D.Skip (ParseChunksState (Either ParseError b) [Array a] s s
-> Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b))
-> ParseChunksState (Either ParseError b) [Array a] s s
-> Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
forall a b. (a -> b) -> a -> b
$ [Array a]
-> [Array a]
-> s
-> ParseChunksState (Either ParseError b) [Array a] s s
forall x inpBuf st pst.
inpBuf -> inpBuf -> pst -> ParseChunksState x inpBuf st pst
ParseChunksExtract [Array a]
xs [] s
pst1
PR.Partial Int
n s
pst1 -> do
Bool -> m () -> m ()
forall a. (?callStack::CallStack) => Bool -> a -> a
assert (Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= [Int] -> Int
forall a. Num a => [a] -> a
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
sum ((Array a -> Int) -> [Array a] -> [Int]
forall a b. (a -> b) -> [a] -> [b]
map Array a -> Int
forall a. Unbox a => Array a -> Int
Array.length (Array a
xArray a -> [Array a] -> [Array a]
forall a. a -> [a] -> [a]
:[Array a]
backBuf))) (() -> m ()
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return ())
let src0 :: [Array a]
src0 = Int -> [Array a] -> [Array a]
forall a. Unbox a => Int -> [Array a] -> [Array a]
takeArrayListRev Int
n (Array a
xArray a -> [Array a] -> [Array a]
forall a. a -> [a] -> [a]
:[Array a]
backBuf)
src :: [Array a]
src = [Array a] -> [Array a]
forall a. [a] -> [a]
Prelude.reverse [Array a]
src0 [Array a] -> [Array a] -> [Array a]
forall a. [a] -> [a] -> [a]
++ [Array a]
xs
Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
-> m (Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b))
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
-> m (Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)))
-> Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
-> m (Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b))
forall a b. (a -> b) -> a -> b
$ ParseChunksState (Either ParseError b) [Array a] s s
-> Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
forall s a. s -> Step s a
D.Skip (ParseChunksState (Either ParseError b) [Array a] s s
-> Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b))
-> ParseChunksState (Either ParseError b) [Array a] s s
-> Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
forall a b. (a -> b) -> a -> b
$ [Array a]
-> [Array a]
-> s
-> ParseChunksState (Either ParseError b) [Array a] s s
forall x inpBuf st pst.
inpBuf -> inpBuf -> pst -> ParseChunksState x inpBuf st pst
ParseChunksExtract [Array a]
src [] s
pst1
PR.Continue Int
0 s
pst1 ->
Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
-> m (Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b))
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
-> m (Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)))
-> Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
-> m (Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b))
forall a b. (a -> b) -> a -> b
$ ParseChunksState (Either ParseError b) [Array a] s s
-> Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
forall s a. s -> Step s a
D.Skip (ParseChunksState (Either ParseError b) [Array a] s s
-> Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b))
-> ParseChunksState (Either ParseError b) [Array a] s s
-> Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
forall a b. (a -> b) -> a -> b
$ [Array a]
-> [Array a]
-> s
-> ParseChunksState (Either ParseError b) [Array a] s s
forall x inpBuf st pst.
inpBuf -> inpBuf -> pst -> ParseChunksState x inpBuf st pst
ParseChunksExtract [Array a]
xs (Array a
xArray a -> [Array a] -> [Array a]
forall a. a -> [a] -> [a]
:[Array a]
backBuf) s
pst1
PR.Continue Int
n s
pst1 -> do
Bool -> m () -> m ()
forall a. (?callStack::CallStack) => Bool -> a -> a
assert (Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= [Int] -> Int
forall a. Num a => [a] -> a
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
sum ((Array a -> Int) -> [Array a] -> [Int]
forall a b. (a -> b) -> [a] -> [b]
map Array a -> Int
forall a. Unbox a => Array a -> Int
Array.length (Array a
xArray a -> [Array a] -> [Array a]
forall a. a -> [a] -> [a]
:[Array a]
backBuf))) (() -> m ()
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return ())
let ([Array a]
src0, [Array a]
buf1) = Int -> [Array a] -> ([Array a], [Array a])
forall a. Unbox a => Int -> [Array a] -> ([Array a], [Array a])
splitAtArrayListRev Int
n (Array a
xArray a -> [Array a] -> [Array a]
forall a. a -> [a] -> [a]
:[Array a]
backBuf)
src :: [Array a]
src = [Array a] -> [Array a]
forall a. [a] -> [a]
Prelude.reverse [Array a]
src0 [Array a] -> [Array a] -> [Array a]
forall a. [a] -> [a] -> [a]
++ [Array a]
xs
Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
-> m (Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b))
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
-> m (Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)))
-> Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
-> m (Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b))
forall a b. (a -> b) -> a -> b
$ ParseChunksState (Either ParseError b) [Array a] s s
-> Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
forall s a. s -> Step s a
D.Skip (ParseChunksState (Either ParseError b) [Array a] s s
-> Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b))
-> ParseChunksState (Either ParseError b) [Array a] s s
-> Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
forall a b. (a -> b) -> a -> b
$ [Array a]
-> [Array a]
-> s
-> ParseChunksState (Either ParseError b) [Array a] s s
forall x inpBuf st pst.
inpBuf -> inpBuf -> pst -> ParseChunksState x inpBuf st pst
ParseChunksExtract [Array a]
src [Array a]
buf1 s
pst1
PR.Done Int
0 b
b ->
Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
-> m (Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b))
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return
(Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
-> m (Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)))
-> Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
-> m (Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b))
forall a b. (a -> b) -> a -> b
$ ParseChunksState (Either ParseError b) [Array a] s s
-> Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
forall s a. s -> Step s a
D.Skip
(ParseChunksState (Either ParseError b) [Array a] s s
-> Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b))
-> ParseChunksState (Either ParseError b) [Array a] s s
-> Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
forall a b. (a -> b) -> a -> b
$ Either ParseError b
-> ParseChunksState (Either ParseError b) [Array a] s s
-> ParseChunksState (Either ParseError b) [Array a] s s
forall x inpBuf st pst.
x
-> ParseChunksState x inpBuf st pst
-> ParseChunksState x inpBuf st pst
ParseChunksYield (b -> Either ParseError b
forall a b. b -> Either a b
Right b
b) ([Array a] -> ParseChunksState (Either ParseError b) [Array a] s s
forall x inpBuf st pst. inpBuf -> ParseChunksState x inpBuf st pst
ParseChunksInitBuf [Array a]
xs)
PR.Done Int
n b
b -> do
Bool -> m () -> m ()
forall a. (?callStack::CallStack) => Bool -> a -> a
assert (Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= [Int] -> Int
forall a. Num a => [a] -> a
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
sum ((Array a -> Int) -> [Array a] -> [Int]
forall a b. (a -> b) -> [a] -> [b]
map Array a -> Int
forall a. Unbox a => Array a -> Int
Array.length (Array a
xArray a -> [Array a] -> [Array a]
forall a. a -> [a] -> [a]
:[Array a]
backBuf))) (() -> m ()
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return ())
let src0 :: [Array a]
src0 = Int -> [Array a] -> [Array a]
forall a. Unbox a => Int -> [Array a] -> [Array a]
takeArrayListRev Int
n (Array a
xArray a -> [Array a] -> [Array a]
forall a. a -> [a] -> [a]
:[Array a]
backBuf)
src :: [Array a]
src = [Array a] -> [Array a]
forall a. [a] -> [a]
Prelude.reverse [Array a]
src0 [Array a] -> [Array a] -> [Array a]
forall a. [a] -> [a] -> [a]
++ [Array a]
xs
Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
-> m (Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b))
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return
(Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
-> m (Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)))
-> Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
-> m (Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b))
forall a b. (a -> b) -> a -> b
$ ParseChunksState (Either ParseError b) [Array a] s s
-> Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
forall s a. s -> Step s a
D.Skip
(ParseChunksState (Either ParseError b) [Array a] s s
-> Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b))
-> ParseChunksState (Either ParseError b) [Array a] s s
-> Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
forall a b. (a -> b) -> a -> b
$ Either ParseError b
-> ParseChunksState (Either ParseError b) [Array a] s s
-> ParseChunksState (Either ParseError b) [Array a] s s
forall x inpBuf st pst.
x
-> ParseChunksState x inpBuf st pst
-> ParseChunksState x inpBuf st pst
ParseChunksYield (b -> Either ParseError b
forall a b. b -> Either a b
Right b
b) ([Array a] -> ParseChunksState (Either ParseError b) [Array a] s s
forall x inpBuf st pst. inpBuf -> ParseChunksState x inpBuf st pst
ParseChunksInitBuf [Array a]
src)
PR.Error String
err -> do
let next :: ParseChunksState x [a] st pst
next = [a] -> ParseChunksState x [a] st pst
forall x inpBuf st pst. inpBuf -> ParseChunksState x inpBuf st pst
ParseChunksInitLeftOver []
Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
-> m (Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b))
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return
(Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
-> m (Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)))
-> Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
-> m (Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b))
forall a b. (a -> b) -> a -> b
$ ParseChunksState (Either ParseError b) [Array a] s s
-> Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
forall s a. s -> Step s a
D.Skip
(ParseChunksState (Either ParseError b) [Array a] s s
-> Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b))
-> ParseChunksState (Either ParseError b) [Array a] s s
-> Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
forall a b. (a -> b) -> a -> b
$ Either ParseError b
-> ParseChunksState (Either ParseError b) [Array a] s s
-> ParseChunksState (Either ParseError b) [Array a] s s
forall x inpBuf st pst.
x
-> ParseChunksState x inpBuf st pst
-> ParseChunksState x inpBuf st pst
ParseChunksYield (ParseError -> Either ParseError b
forall a b. a -> Either a b
Left (String -> ParseError
ParseError String
err)) ParseChunksState (Either ParseError b) [Array a] s s
forall {x} {a} {st} {pst}. ParseChunksState x [a] st pst
next
stepOuter State StreamK m a
_ (ParseChunksStop [Array a]
backBuf s
pst) = do
Step s b
pRes <- s -> m (Step s b)
extract s
pst
case Step s b
pRes of
PR.Partial Int
_ s
_ -> String
-> m (Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b))
forall a. (?callStack::CallStack) => String -> a
error String
"runArrayFoldManyD: Partial in extract"
PR.Continue Int
0 s
pst1 ->
Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
-> m (Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b))
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
-> m (Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)))
-> Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
-> m (Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b))
forall a b. (a -> b) -> a -> b
$ ParseChunksState (Either ParseError b) [Array a] s s
-> Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
forall s a. s -> Step s a
D.Skip (ParseChunksState (Either ParseError b) [Array a] s s
-> Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b))
-> ParseChunksState (Either ParseError b) [Array a] s s
-> Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
forall a b. (a -> b) -> a -> b
$ [Array a]
-> s -> ParseChunksState (Either ParseError b) [Array a] s s
forall x inpBuf st pst.
inpBuf -> pst -> ParseChunksState x inpBuf st pst
ParseChunksStop [Array a]
backBuf s
pst1
PR.Continue Int
n s
pst1 -> do
Bool -> m () -> m ()
forall a. (?callStack::CallStack) => Bool -> a -> a
assert (Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= [Int] -> Int
forall a. Num a => [a] -> a
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
sum ((Array a -> Int) -> [Array a] -> [Int]
forall a b. (a -> b) -> [a] -> [b]
map Array a -> Int
forall a. Unbox a => Array a -> Int
Array.length [Array a]
backBuf)) (() -> m ()
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return ())
let ([Array a]
src0, [Array a]
buf1) = Int -> [Array a] -> ([Array a], [Array a])
forall a. Unbox a => Int -> [Array a] -> ([Array a], [Array a])
splitAtArrayListRev Int
n [Array a]
backBuf
src :: [Array a]
src = [Array a] -> [Array a]
forall a. [a] -> [a]
Prelude.reverse [Array a]
src0
Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
-> m (Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b))
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
-> m (Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)))
-> Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
-> m (Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b))
forall a b. (a -> b) -> a -> b
$ ParseChunksState (Either ParseError b) [Array a] s s
-> Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
forall s a. s -> Step s a
D.Skip (ParseChunksState (Either ParseError b) [Array a] s s
-> Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b))
-> ParseChunksState (Either ParseError b) [Array a] s s
-> Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
forall a b. (a -> b) -> a -> b
$ [Array a]
-> [Array a]
-> s
-> ParseChunksState (Either ParseError b) [Array a] s s
forall x inpBuf st pst.
inpBuf -> inpBuf -> pst -> ParseChunksState x inpBuf st pst
ParseChunksExtract [Array a]
src [Array a]
buf1 s
pst1
PR.Done Int
0 b
b ->
Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
-> m (Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b))
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return
(Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
-> m (Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)))
-> Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
-> m (Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b))
forall a b. (a -> b) -> a -> b
$ ParseChunksState (Either ParseError b) [Array a] s s
-> Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
forall s a. s -> Step s a
D.Skip
(ParseChunksState (Either ParseError b) [Array a] s s
-> Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b))
-> ParseChunksState (Either ParseError b) [Array a] s s
-> Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
forall a b. (a -> b) -> a -> b
$ Either ParseError b
-> ParseChunksState (Either ParseError b) [Array a] s s
-> ParseChunksState (Either ParseError b) [Array a] s s
forall x inpBuf st pst.
x
-> ParseChunksState x inpBuf st pst
-> ParseChunksState x inpBuf st pst
ParseChunksYield (b -> Either ParseError b
forall a b. b -> Either a b
Right b
b) ([Array a] -> ParseChunksState (Either ParseError b) [Array a] s s
forall x inpBuf st pst. inpBuf -> ParseChunksState x inpBuf st pst
ParseChunksInitLeftOver [])
PR.Done Int
n b
b -> do
Bool -> m () -> m ()
forall a. (?callStack::CallStack) => Bool -> a -> a
assert (Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= [Int] -> Int
forall a. Num a => [a] -> a
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
sum ((Array a -> Int) -> [Array a] -> [Int]
forall a b. (a -> b) -> [a] -> [b]
map Array a -> Int
forall a. Unbox a => Array a -> Int
Array.length [Array a]
backBuf)) (() -> m ()
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return ())
let src0 :: [Array a]
src0 = Int -> [Array a] -> [Array a]
forall a. Unbox a => Int -> [Array a] -> [Array a]
takeArrayListRev Int
n [Array a]
backBuf
src :: [Array a]
src = [Array a] -> [Array a]
forall a. [a] -> [a]
Prelude.reverse [Array a]
src0
Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
-> m (Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b))
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return
(Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
-> m (Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)))
-> Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
-> m (Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b))
forall a b. (a -> b) -> a -> b
$ ParseChunksState (Either ParseError b) [Array a] s s
-> Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
forall s a. s -> Step s a
D.Skip
(ParseChunksState (Either ParseError b) [Array a] s s
-> Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b))
-> ParseChunksState (Either ParseError b) [Array a] s s
-> Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
forall a b. (a -> b) -> a -> b
$ Either ParseError b
-> ParseChunksState (Either ParseError b) [Array a] s s
-> ParseChunksState (Either ParseError b) [Array a] s s
forall x inpBuf st pst.
x
-> ParseChunksState x inpBuf st pst
-> ParseChunksState x inpBuf st pst
ParseChunksYield (b -> Either ParseError b
forall a b. b -> Either a b
Right b
b) ([Array a] -> ParseChunksState (Either ParseError b) [Array a] s s
forall x inpBuf st pst. inpBuf -> ParseChunksState x inpBuf st pst
ParseChunksInitBuf [Array a]
src)
PR.Error String
err -> do
let next :: ParseChunksState x [a] st pst
next = [a] -> ParseChunksState x [a] st pst
forall x inpBuf st pst. inpBuf -> ParseChunksState x inpBuf st pst
ParseChunksInitLeftOver []
Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
-> m (Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b))
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return
(Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
-> m (Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)))
-> Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
-> m (Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b))
forall a b. (a -> b) -> a -> b
$ ParseChunksState (Either ParseError b) [Array a] s s
-> Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
forall s a. s -> Step s a
D.Skip
(ParseChunksState (Either ParseError b) [Array a] s s
-> Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b))
-> ParseChunksState (Either ParseError b) [Array a] s s
-> Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
forall a b. (a -> b) -> a -> b
$ Either ParseError b
-> ParseChunksState (Either ParseError b) [Array a] s s
-> ParseChunksState (Either ParseError b) [Array a] s s
forall x inpBuf st pst.
x
-> ParseChunksState x inpBuf st pst
-> ParseChunksState x inpBuf st pst
ParseChunksYield (ParseError -> Either ParseError b
forall a b. a -> Either a b
Left (String -> ParseError
ParseError String
err)) ParseChunksState (Either ParseError b) [Array a] s s
forall {x} {a} {st} {pst}. ParseChunksState x [a] st pst
next
stepOuter State StreamK m a
_ (ParseChunksYield Either ParseError b
a ParseChunksState (Either ParseError b) [Array a] s s
next) = Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
-> m (Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b))
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
-> m (Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)))
-> Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
-> m (Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b))
forall a b. (a -> b) -> a -> b
$ Either ParseError b
-> ParseChunksState (Either ParseError b) [Array a] s s
-> Step
(ParseChunksState (Either ParseError b) [Array a] s s)
(Either ParseError b)
forall s a. a -> s -> Step s a
D.Yield Either ParseError b
a ParseChunksState (Either ParseError b) [Array a] s s
next
{-# INLINE runArrayFoldMany #-}
runArrayFoldMany
:: (Monad m, Unbox a)
=> ChunkFold m a b
-> StreamK m (Array a)
-> StreamK m (Either ParseError b)
runArrayFoldMany :: forall (m :: * -> *) a b.
(Monad m, Unbox a) =>
ChunkFold m a b
-> StreamK m (Array a) -> StreamK m (Either ParseError b)
runArrayFoldMany ChunkFold m a b
p StreamK m (Array a)
m = Stream m (Either ParseError b) -> StreamK m (Either ParseError b)
forall (m :: * -> *) a. Monad m => Stream m a -> StreamK m a
fromStream (Stream m (Either ParseError b) -> StreamK m (Either ParseError b))
-> Stream m (Either ParseError b)
-> StreamK m (Either ParseError b)
forall a b. (a -> b) -> a -> b
$ ChunkFold m a b
-> Stream m (Array a) -> Stream m (Either ParseError b)
forall (m :: * -> *) a b.
(Monad m, Unbox a) =>
ChunkFold m a b
-> Stream m (Array a) -> Stream m (Either ParseError b)
runArrayFoldManyD ChunkFold m a b
p (StreamK m (Array a) -> Stream m (Array a)
forall (m :: * -> *) a. Applicative m => StreamK m a -> Stream m a
toStream StreamK m (Array a)
m)