{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE UndecidableInstances #-}
module Dahdit.Run
( GetError (..)
, prettyGetError
, runGetInternal
, GetIncEnv (..)
, newGetIncEnv
, GetIncChunk (..)
, GetIncRequest (..)
, GetIncSuspend (..)
, GetIncCb
, runGetIncInternal
, runCount
, runPutInternal
)
where
import Control.Applicative (Alternative (..))
import Control.Exception (Exception (..))
import Control.Monad (replicateM_, unless)
import Control.Monad.Except (ExceptT, MonadError, runExceptT, throwError)
import Control.Monad.Free.Church (F (..), iterM)
import Control.Monad.Free.Class (MonadFree (..))
import Control.Monad.Primitive (MonadPrim, PrimMonad (..))
import Control.Monad.Reader (MonadReader (..), ReaderT (..), asks)
import Control.Monad.State.Strict (MonadState, State, runState)
import qualified Control.Monad.State.Strict as State
import Control.Monad.Trans (MonadTrans (..))
import Control.Monad.Trans.Free.Church (FT (..), iterT)
import Control.Monad.Trans.Maybe (MaybeT (..))
import Dahdit.Free
( Get (..)
, GetF (..)
, GetLookAheadF (..)
, GetScopeF (..)
, GetStaticArrayF (..)
, GetStaticSeqF (..)
, Put
, PutF (..)
, PutM (..)
, PutStaticArrayF (..)
, PutStaticHintF (..)
, PutStaticSeqF (..)
, ScopeMode (..)
)
import Dahdit.Mem (ReadMem (..), WriteMem (..), readSBSMem, writeSBSMem)
import Dahdit.Nums
( DoubleBE
, DoubleLE
, FloatBE
, FloatLE
, Int16BE
, Int16LE (..)
, Int24BE
, Int24LE
, Int32BE
, Int32LE
, Int64BE
, Int64LE
, Word16BE
, Word16LE (..)
, Word24BE
, Word24LE
, Word32BE
, Word32LE
, Word64BE
, Word64LE
)
import Dahdit.Proxy (proxyForF)
import Dahdit.Sizes (ByteCount (..), ElemCount (..), primByteSizeOf, staticByteSize)
import Data.Coerce (coerce)
import Data.Foldable (for_, toList)
import Data.Int (Int8)
import Data.Maybe (fromJust)
import Data.Primitive.ByteArray (ByteArray (..))
import Data.Primitive.MutVar (MutVar, modifyMutVar', newMutVar, readMutVar, writeMutVar)
import Data.Primitive.PrimArray (PrimArray (..), sizeofPrimArray)
import Data.Sequence (Seq (..))
import qualified Data.Sequence as Seq
import Data.Text (Text)
import qualified Data.Text as T
import Data.Word (Word8)
getStaticSeqSize :: GetStaticSeqF a -> ByteCount
getStaticSeqSize :: forall a. GetStaticSeqF a -> ByteCount
getStaticSeqSize (GetStaticSeqF ElemCount
ec Get z
g Seq z -> a
_) = Proxy z -> ByteCount
forall a. StaticByteSized a => Proxy a -> ByteCount
staticByteSize (Get z -> Proxy z
forall (f :: * -> *) a. f a -> Proxy a
proxyForF Get z
g) ByteCount -> ByteCount -> ByteCount
forall a. Num a => a -> a -> a
* ElemCount -> ByteCount
forall a b. Coercible a b => a -> b
coerce ElemCount
ec
getStaticArraySize :: GetStaticArrayF a -> ByteCount
getStaticArraySize :: forall a. GetStaticArrayF a -> ByteCount
getStaticArraySize (GetStaticArrayF ElemCount
n Proxy z
prox PrimArray z -> a
_) = Proxy z -> ByteCount
forall a. Prim a => Proxy a -> ByteCount
primByteSizeOf Proxy z
prox ByteCount -> ByteCount -> ByteCount
forall a. Num a => a -> a -> a
* ElemCount -> ByteCount
forall a b. Coercible a b => a -> b
coerce ElemCount
n
putStaticSeqSize :: PutStaticSeqF a -> ByteCount
putStaticSeqSize :: forall a. PutStaticSeqF a -> ByteCount
putStaticSeqSize (PutStaticSeqF ElemCount
n Maybe z
_ z -> Put
_ Seq z
s a
_) = Proxy z -> ByteCount
forall a. StaticByteSized a => Proxy a -> ByteCount
staticByteSize (Seq z -> Proxy z
forall (f :: * -> *) a. f a -> Proxy a
proxyForF Seq z
s) ByteCount -> ByteCount -> ByteCount
forall a. Num a => a -> a -> a
* ElemCount -> ByteCount
forall a b. Coercible a b => a -> b
coerce ElemCount
n
putStaticArrayElemSize :: PutStaticArrayF a -> ByteCount
putStaticArrayElemSize :: forall a. PutStaticArrayF a -> ByteCount
putStaticArrayElemSize (PutStaticArrayF ElemCount
_ Maybe z
_ PrimArray z
zs a
_) = Proxy z -> ByteCount
forall a. Prim a => Proxy a -> ByteCount
primByteSizeOf (PrimArray z -> Proxy z
forall (f :: * -> *) a. f a -> Proxy a
proxyForF PrimArray z
zs)
putStaticArraySize :: PutStaticArrayF a -> ByteCount
putStaticArraySize :: forall a. PutStaticArrayF a -> ByteCount
putStaticArraySize (PutStaticArrayF ElemCount
n Maybe z
_ PrimArray z
zs a
_) = Proxy z -> ByteCount
forall a. Prim a => Proxy a -> ByteCount
primByteSizeOf (PrimArray z -> Proxy z
forall (f :: * -> *) a. f a -> Proxy a
proxyForF PrimArray z
zs) ByteCount -> ByteCount -> ByteCount
forall a. Num a => a -> a -> a
* ElemCount -> ByteCount
forall a b. Coercible a b => a -> b
coerce ElemCount
n
data GetError
= GetErrorLocalCap !Text !ByteCount !ByteCount
| GetErrorScopedMismatch !ScopeMode !ByteCount !ByteCount
| GetErrorFail !Text
| GetErrorGlobalCap !Text !ByteCount !ByteCount
| GetErrorRemaining !ByteCount
deriving stock (GetError -> GetError -> Bool
(GetError -> GetError -> Bool)
-> (GetError -> GetError -> Bool) -> Eq GetError
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: GetError -> GetError -> Bool
== :: GetError -> GetError -> Bool
$c/= :: GetError -> GetError -> Bool
/= :: GetError -> GetError -> Bool
Eq, Int -> GetError -> ShowS
[GetError] -> ShowS
GetError -> String
(Int -> GetError -> ShowS)
-> (GetError -> String) -> ([GetError] -> ShowS) -> Show GetError
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> GetError -> ShowS
showsPrec :: Int -> GetError -> ShowS
$cshow :: GetError -> String
show :: GetError -> String
$cshowList :: [GetError] -> ShowS
showList :: [GetError] -> ShowS
Show)
instance Exception GetError where
displayException :: GetError -> String
displayException = Text -> String
T.unpack (Text -> String) -> (GetError -> Text) -> GetError -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GetError -> Text
prettyGetError
prettyGetError :: GetError -> Text
prettyGetError :: GetError -> Text
prettyGetError = \case
GetErrorLocalCap Text
nm ByteCount
ac ByteCount
bc ->
Text
"End of chunk parsing "
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
nm
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
" (have "
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> String -> Text
T.pack (Int -> String
forall a. Show a => a -> String
show (ByteCount -> Int
unByteCount ByteCount
ac))
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
" bytes, need "
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> String -> Text
T.pack (Int -> String
forall a. Show a => a -> String
show (ByteCount -> Int
unByteCount ByteCount
bc))
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
")"
GetErrorScopedMismatch ScopeMode
sm ByteCount
ac ByteCount
bc ->
let ty :: Text
ty = case ScopeMode
sm of ScopeMode
ScopeModeExact -> Text
"exact"; ScopeMode
ScopeModeWithin -> Text
"within"
in Text
"Did not parse "
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
ty
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
" scoped input (read "
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> String -> Text
T.pack (Int -> String
forall a. Show a => a -> String
show (ByteCount -> Int
unByteCount ByteCount
ac))
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
" bytes, expected "
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> String -> Text
T.pack (Int -> String
forall a. Show a => a -> String
show (ByteCount -> Int
unByteCount ByteCount
bc))
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
")"
GetErrorFail Text
msg -> Text
"User error: " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
msg
GetErrorGlobalCap Text
nm ByteCount
ac ByteCount
bc ->
Text
"Hit limit parsing "
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
nm
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
" (allowed "
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> String -> Text
T.pack (Int -> String
forall a. Show a => a -> String
show (ByteCount -> Int
unByteCount ByteCount
ac))
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
" bytes, need "
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> String -> Text
T.pack (Int -> String
forall a. Show a => a -> String
show (ByteCount -> Int
unByteCount ByteCount
bc))
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
")"
GetErrorRemaining ByteCount
ac -> Text
"Cannot read remaining length in stream context (read " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> String -> Text
T.pack (Int -> String
forall a. Show a => a -> String
show (ByteCount -> Int
unByteCount ByteCount
ac)) Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
")"
runGetInternal :: (ReadMem r m) => ByteCount -> Get a -> ByteCount -> r -> m (Either GetError a, ByteCount)
runGetInternal :: forall r (m :: * -> *) a.
ReadMem r m =>
ByteCount
-> Get a -> ByteCount -> r -> m (Either GetError a, ByteCount)
runGetInternal ByteCount
off Get a
act ByteCount
cap r
mem = do
let chunk :: GetIncChunk r
chunk = ByteCount -> ByteCount -> r -> GetIncChunk r
forall r. ByteCount -> ByteCount -> r -> GetIncChunk r
GetIncChunk ByteCount
off ByteCount
cap r
mem
GetIncEnv (PrimState m) r
env <- Maybe ByteCount -> GetIncChunk r -> m (GetIncEnv (PrimState m) r)
forall s (m :: * -> *) r.
MonadPrim s m =>
Maybe ByteCount -> GetIncChunk r -> m (GetIncEnv s r)
newGetIncEnv (ByteCount -> Maybe ByteCount
forall a. a -> Maybe a
Just (ByteCount
cap ByteCount -> ByteCount -> ByteCount
forall a. Num a => a -> a -> a
- ByteCount
off)) GetIncChunk r
chunk
(Either GetError a
ea, ByteCount
_, ByteCount
off') <- Get a
-> GetIncEnv (PrimState m) r
-> GetIncCbChunk r m
-> m (Either GetError a, ByteCount, ByteCount)
forall s (m :: * -> *) r a.
(MonadPrim s m, ReadMem r m) =>
Get a
-> GetIncEnv s r
-> GetIncCbChunk r m
-> m (Either GetError a, ByteCount, ByteCount)
runGetIncInternal Get a
act GetIncEnv (PrimState m) r
env (m (Maybe (GetIncChunk r)) -> GetIncCbChunk r m
forall a b. a -> b -> a
const (Maybe (GetIncChunk r) -> m (Maybe (GetIncChunk r))
forall a. a -> m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe (GetIncChunk r)
forall a. Maybe a
Nothing))
(Either GetError a, ByteCount) -> m (Either GetError a, ByteCount)
forall a. a -> m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Either GetError a
ea, ByteCount
off')
data GetIncChunk r = GetIncChunk
{ forall r. GetIncChunk r -> ByteCount
gicLocalOff :: !ByteCount
, forall r. GetIncChunk r -> ByteCount
gicLocalCap :: !ByteCount
, forall r. GetIncChunk r -> r
gicArray :: !r
}
data GetIncEnv s r = GetIncEnv
{ forall s r. GetIncEnv s r -> MutVar s ByteCount
gieGlobalAbs :: !(MutVar s ByteCount)
, forall s r. GetIncEnv s r -> MutVar s ByteCount
gieGlobalRel :: !(MutVar s ByteCount)
, forall s r. GetIncEnv s r -> MutVar s (Seq ByteCount)
gieGlobalCap :: !(MutVar s (Seq ByteCount))
, forall s r. GetIncEnv s r -> MutVar s (GetIncChunk r)
gieCurChunk :: !(MutVar s (GetIncChunk r))
, forall s r. GetIncEnv s r -> MutVar s (Seq ByteCount)
gieLookAhead :: !(MutVar s (Seq ByteCount))
}
newGetIncEnv :: (MonadPrim s m) => Maybe ByteCount -> GetIncChunk r -> m (GetIncEnv s r)
newGetIncEnv :: forall s (m :: * -> *) r.
MonadPrim s m =>
Maybe ByteCount -> GetIncChunk r -> m (GetIncEnv s r)
newGetIncEnv Maybe ByteCount
mayCap GetIncChunk r
chunk = do
MutVar s ByteCount
gloAbsVar <- ByteCount -> m (MutVar (PrimState m) ByteCount)
forall (m :: * -> *) a.
PrimMonad m =>
a -> m (MutVar (PrimState m) a)
newMutVar ByteCount
0
MutVar s ByteCount
gloRelVar <- ByteCount -> m (MutVar (PrimState m) ByteCount)
forall (m :: * -> *) a.
PrimMonad m =>
a -> m (MutVar (PrimState m) a)
newMutVar ByteCount
0
MutVar s (Seq ByteCount)
gloCapVar <- Seq ByteCount -> m (MutVar (PrimState m) (Seq ByteCount))
forall (m :: * -> *) a.
PrimMonad m =>
a -> m (MutVar (PrimState m) a)
newMutVar (Seq ByteCount
-> (ByteCount -> Seq ByteCount) -> Maybe ByteCount -> Seq ByteCount
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Seq ByteCount
forall a. Seq a
Empty ByteCount -> Seq ByteCount
forall a. a -> Seq a
Seq.singleton Maybe ByteCount
mayCap)
MutVar s (GetIncChunk r)
curChunkVar <- GetIncChunk r -> m (MutVar (PrimState m) (GetIncChunk r))
forall (m :: * -> *) a.
PrimMonad m =>
a -> m (MutVar (PrimState m) a)
newMutVar GetIncChunk r
chunk
MutVar s (Seq ByteCount)
lookAheadVar <- Seq ByteCount -> m (MutVar (PrimState m) (Seq ByteCount))
forall (m :: * -> *) a.
PrimMonad m =>
a -> m (MutVar (PrimState m) a)
newMutVar Seq ByteCount
forall a. Seq a
Empty
GetIncEnv s r -> m (GetIncEnv s r)
forall a. a -> m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (MutVar s ByteCount
-> MutVar s ByteCount
-> MutVar s (Seq ByteCount)
-> MutVar s (GetIncChunk r)
-> MutVar s (Seq ByteCount)
-> GetIncEnv s r
forall s r.
MutVar s ByteCount
-> MutVar s ByteCount
-> MutVar s (Seq ByteCount)
-> MutVar s (GetIncChunk r)
-> MutVar s (Seq ByteCount)
-> GetIncEnv s r
GetIncEnv MutVar s ByteCount
gloAbsVar MutVar s ByteCount
gloRelVar MutVar s (Seq ByteCount)
gloCapVar MutVar s (GetIncChunk r)
curChunkVar MutVar s (Seq ByteCount)
lookAheadVar)
data GetIncRequest = GetIncRequest
{ GetIncRequest -> ByteCount
girAbsPos :: !ByteCount
, GetIncRequest -> ByteCount
girBaseOff :: !ByteCount
, GetIncRequest -> ByteCount
girNeedLength :: !ByteCount
}
deriving stock (GetIncRequest -> GetIncRequest -> Bool
(GetIncRequest -> GetIncRequest -> Bool)
-> (GetIncRequest -> GetIncRequest -> Bool) -> Eq GetIncRequest
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: GetIncRequest -> GetIncRequest -> Bool
== :: GetIncRequest -> GetIncRequest -> Bool
$c/= :: GetIncRequest -> GetIncRequest -> Bool
/= :: GetIncRequest -> GetIncRequest -> Bool
Eq, Eq GetIncRequest
Eq GetIncRequest =>
(GetIncRequest -> GetIncRequest -> Ordering)
-> (GetIncRequest -> GetIncRequest -> Bool)
-> (GetIncRequest -> GetIncRequest -> Bool)
-> (GetIncRequest -> GetIncRequest -> Bool)
-> (GetIncRequest -> GetIncRequest -> Bool)
-> (GetIncRequest -> GetIncRequest -> GetIncRequest)
-> (GetIncRequest -> GetIncRequest -> GetIncRequest)
-> Ord GetIncRequest
GetIncRequest -> GetIncRequest -> Bool
GetIncRequest -> GetIncRequest -> Ordering
GetIncRequest -> GetIncRequest -> GetIncRequest
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: GetIncRequest -> GetIncRequest -> Ordering
compare :: GetIncRequest -> GetIncRequest -> Ordering
$c< :: GetIncRequest -> GetIncRequest -> Bool
< :: GetIncRequest -> GetIncRequest -> Bool
$c<= :: GetIncRequest -> GetIncRequest -> Bool
<= :: GetIncRequest -> GetIncRequest -> Bool
$c> :: GetIncRequest -> GetIncRequest -> Bool
> :: GetIncRequest -> GetIncRequest -> Bool
$c>= :: GetIncRequest -> GetIncRequest -> Bool
>= :: GetIncRequest -> GetIncRequest -> Bool
$cmax :: GetIncRequest -> GetIncRequest -> GetIncRequest
max :: GetIncRequest -> GetIncRequest -> GetIncRequest
$cmin :: GetIncRequest -> GetIncRequest -> GetIncRequest
min :: GetIncRequest -> GetIncRequest -> GetIncRequest
Ord, Int -> GetIncRequest -> ShowS
[GetIncRequest] -> ShowS
GetIncRequest -> String
(Int -> GetIncRequest -> ShowS)
-> (GetIncRequest -> String)
-> ([GetIncRequest] -> ShowS)
-> Show GetIncRequest
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> GetIncRequest -> ShowS
showsPrec :: Int -> GetIncRequest -> ShowS
$cshow :: GetIncRequest -> String
show :: GetIncRequest -> String
$cshowList :: [GetIncRequest] -> ShowS
showList :: [GetIncRequest] -> ShowS
Show)
data GetIncSuspend z x = GetIncSuspend !GetIncRequest !(Maybe z -> x)
deriving stock ((forall a b. (a -> b) -> GetIncSuspend z a -> GetIncSuspend z b)
-> (forall a b. a -> GetIncSuspend z b -> GetIncSuspend z a)
-> Functor (GetIncSuspend z)
forall a b. a -> GetIncSuspend z b -> GetIncSuspend z a
forall a b. (a -> b) -> GetIncSuspend z a -> GetIncSuspend z b
forall z a b. a -> GetIncSuspend z b -> GetIncSuspend z a
forall z a b. (a -> b) -> GetIncSuspend z a -> GetIncSuspend z b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
$cfmap :: forall z a b. (a -> b) -> GetIncSuspend z a -> GetIncSuspend z b
fmap :: forall a b. (a -> b) -> GetIncSuspend z a -> GetIncSuspend z b
$c<$ :: forall z a b. a -> GetIncSuspend z b -> GetIncSuspend z a
<$ :: forall a b. a -> GetIncSuspend z b -> GetIncSuspend z a
Functor)
type GetIncSuspendChunk r = GetIncSuspend (GetIncChunk r)
newtype GetIncM s r m a = GetIncM {forall s r (m :: * -> *) a.
GetIncM s r m a
-> ReaderT
(GetIncEnv s r) (ExceptT GetError (FT (GetIncSuspendChunk r) m)) a
unGetIncM :: ReaderT (GetIncEnv s r) (ExceptT GetError (FT (GetIncSuspendChunk r) m)) a}
deriving newtype
( (forall a b. (a -> b) -> GetIncM s r m a -> GetIncM s r m b)
-> (forall a b. a -> GetIncM s r m b -> GetIncM s r m a)
-> Functor (GetIncM s r m)
forall a b. a -> GetIncM s r m b -> GetIncM s r m a
forall a b. (a -> b) -> GetIncM s r m a -> GetIncM s r m b
forall s r (m :: * -> *) a b.
a -> GetIncM s r m b -> GetIncM s r m a
forall s r (m :: * -> *) a b.
(a -> b) -> GetIncM s r m a -> GetIncM s r m b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
$cfmap :: forall s r (m :: * -> *) a b.
(a -> b) -> GetIncM s r m a -> GetIncM s r m b
fmap :: forall a b. (a -> b) -> GetIncM s r m a -> GetIncM s r m b
$c<$ :: forall s r (m :: * -> *) a b.
a -> GetIncM s r m b -> GetIncM s r m a
<$ :: forall a b. a -> GetIncM s r m b -> GetIncM s r m a
Functor
, Functor (GetIncM s r m)
Functor (GetIncM s r m) =>
(forall a. a -> GetIncM s r m a)
-> (forall a b.
GetIncM s r m (a -> b) -> GetIncM s r m a -> GetIncM s r m b)
-> (forall a b c.
(a -> b -> c)
-> GetIncM s r m a -> GetIncM s r m b -> GetIncM s r m c)
-> (forall a b.
GetIncM s r m a -> GetIncM s r m b -> GetIncM s r m b)
-> (forall a b.
GetIncM s r m a -> GetIncM s r m b -> GetIncM s r m a)
-> Applicative (GetIncM s r m)
forall a. a -> GetIncM s r m a
forall a b. GetIncM s r m a -> GetIncM s r m b -> GetIncM s r m a
forall a b. GetIncM s r m a -> GetIncM s r m b -> GetIncM s r m b
forall a b.
GetIncM s r m (a -> b) -> GetIncM s r m a -> GetIncM s r m b
forall a b c.
(a -> b -> c)
-> GetIncM s r m a -> GetIncM s r m b -> GetIncM s r m c
forall s r (m :: * -> *). Functor (GetIncM s r m)
forall s r (m :: * -> *) a. a -> GetIncM s r m a
forall s r (m :: * -> *) a b.
GetIncM s r m a -> GetIncM s r m b -> GetIncM s r m a
forall s r (m :: * -> *) a b.
GetIncM s r m a -> GetIncM s r m b -> GetIncM s r m b
forall s r (m :: * -> *) a b.
GetIncM s r m (a -> b) -> GetIncM s r m a -> GetIncM s r m b
forall s r (m :: * -> *) a b c.
(a -> b -> c)
-> GetIncM s r m a -> GetIncM s r m b -> GetIncM s r m c
forall (f :: * -> *).
Functor f =>
(forall a. a -> f a)
-> (forall a b. f (a -> b) -> f a -> f b)
-> (forall a b c. (a -> b -> c) -> f a -> f b -> f c)
-> (forall a b. f a -> f b -> f b)
-> (forall a b. f a -> f b -> f a)
-> Applicative f
$cpure :: forall s r (m :: * -> *) a. a -> GetIncM s r m a
pure :: forall a. a -> GetIncM s r m a
$c<*> :: forall s r (m :: * -> *) a b.
GetIncM s r m (a -> b) -> GetIncM s r m a -> GetIncM s r m b
<*> :: forall a b.
GetIncM s r m (a -> b) -> GetIncM s r m a -> GetIncM s r m b
$cliftA2 :: forall s r (m :: * -> *) a b c.
(a -> b -> c)
-> GetIncM s r m a -> GetIncM s r m b -> GetIncM s r m c
liftA2 :: forall a b c.
(a -> b -> c)
-> GetIncM s r m a -> GetIncM s r m b -> GetIncM s r m c
$c*> :: forall s r (m :: * -> *) a b.
GetIncM s r m a -> GetIncM s r m b -> GetIncM s r m b
*> :: forall a b. GetIncM s r m a -> GetIncM s r m b -> GetIncM s r m b
$c<* :: forall s r (m :: * -> *) a b.
GetIncM s r m a -> GetIncM s r m b -> GetIncM s r m a
<* :: forall a b. GetIncM s r m a -> GetIncM s r m b -> GetIncM s r m a
Applicative
, Applicative (GetIncM s r m)
Applicative (GetIncM s r m) =>
(forall a b.
GetIncM s r m a -> (a -> GetIncM s r m b) -> GetIncM s r m b)
-> (forall a b.
GetIncM s r m a -> GetIncM s r m b -> GetIncM s r m b)
-> (forall a. a -> GetIncM s r m a)
-> Monad (GetIncM s r m)
forall a. a -> GetIncM s r m a
forall a b. GetIncM s r m a -> GetIncM s r m b -> GetIncM s r m b
forall a b.
GetIncM s r m a -> (a -> GetIncM s r m b) -> GetIncM s r m b
forall s r (m :: * -> *). Applicative (GetIncM s r m)
forall s r (m :: * -> *) a. a -> GetIncM s r m a
forall s r (m :: * -> *) a b.
GetIncM s r m a -> GetIncM s r m b -> GetIncM s r m b
forall s r (m :: * -> *) a b.
GetIncM s r m a -> (a -> GetIncM s r m b) -> GetIncM s r m b
forall (m :: * -> *).
Applicative m =>
(forall a b. m a -> (a -> m b) -> m b)
-> (forall a b. m a -> m b -> m b)
-> (forall a. a -> m a)
-> Monad m
$c>>= :: forall s r (m :: * -> *) a b.
GetIncM s r m a -> (a -> GetIncM s r m b) -> GetIncM s r m b
>>= :: forall a b.
GetIncM s r m a -> (a -> GetIncM s r m b) -> GetIncM s r m b
$c>> :: forall s r (m :: * -> *) a b.
GetIncM s r m a -> GetIncM s r m b -> GetIncM s r m b
>> :: forall a b. GetIncM s r m a -> GetIncM s r m b -> GetIncM s r m b
$creturn :: forall s r (m :: * -> *) a. a -> GetIncM s r m a
return :: forall a. a -> GetIncM s r m a
Monad
, MonadError GetError
, MonadFree (GetIncSuspendChunk r)
)
instance MonadTrans (GetIncM s r) where
lift :: forall (m :: * -> *) a. Monad m => m a -> GetIncM s r m a
lift = ReaderT
(GetIncEnv s r) (ExceptT GetError (FT (GetIncSuspendChunk r) m)) a
-> GetIncM s r m a
forall s r (m :: * -> *) a.
ReaderT
(GetIncEnv s r) (ExceptT GetError (FT (GetIncSuspendChunk r) m)) a
-> GetIncM s r m a
GetIncM (ReaderT
(GetIncEnv s r) (ExceptT GetError (FT (GetIncSuspendChunk r) m)) a
-> GetIncM s r m a)
-> (m a
-> ReaderT
(GetIncEnv s r) (ExceptT GetError (FT (GetIncSuspendChunk r) m)) a)
-> m a
-> GetIncM s r m a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ExceptT GetError (FT (GetIncSuspendChunk r) m) a
-> ReaderT
(GetIncEnv s r) (ExceptT GetError (FT (GetIncSuspendChunk r) m)) a
forall (m :: * -> *) a.
Monad m =>
m a -> ReaderT (GetIncEnv s r) m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (ExceptT GetError (FT (GetIncSuspendChunk r) m) a
-> ReaderT
(GetIncEnv s r) (ExceptT GetError (FT (GetIncSuspendChunk r) m)) a)
-> (m a -> ExceptT GetError (FT (GetIncSuspendChunk r) m) a)
-> m a
-> ReaderT
(GetIncEnv s r) (ExceptT GetError (FT (GetIncSuspendChunk r) m)) a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FT (GetIncSuspendChunk r) m a
-> ExceptT GetError (FT (GetIncSuspendChunk r) m) a
forall (m :: * -> *) a. Monad m => m a -> ExceptT GetError m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (FT (GetIncSuspendChunk r) m a
-> ExceptT GetError (FT (GetIncSuspendChunk r) m) a)
-> (m a -> FT (GetIncSuspendChunk r) m a)
-> m a
-> ExceptT GetError (FT (GetIncSuspendChunk r) m) a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. m a -> FT (GetIncSuspendChunk r) m a
forall (m :: * -> *) a.
Monad m =>
m a -> FT (GetIncSuspendChunk r) m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift
type GetIncCb z m = GetIncRequest -> m (Maybe z)
type GetIncCbChunk r m = GetIncCb (GetIncChunk r) m
pushMutVar :: (MonadPrim s m) => MutVar s (Seq a) -> a -> m ()
pushMutVar :: forall s (m :: * -> *) a.
MonadPrim s m =>
MutVar s (Seq a) -> a -> m ()
pushMutVar MutVar s (Seq a)
v a
a = MutVar (PrimState m) (Seq a) -> (Seq a -> Seq a) -> m ()
forall (m :: * -> *) a.
PrimMonad m =>
MutVar (PrimState m) a -> (a -> a) -> m ()
modifyMutVar' MutVar s (Seq a)
MutVar (PrimState m) (Seq a)
v (Seq a -> a -> Seq a
forall a. Seq a -> a -> Seq a
:|> a
a)
popMutVar :: (MonadPrim s m) => MutVar s (Seq a) -> m ()
popMutVar :: forall s (m :: * -> *) a. MonadPrim s m => MutVar s (Seq a) -> m ()
popMutVar MutVar s (Seq a)
v = MutVar (PrimState m) (Seq a) -> (Seq a -> Seq a) -> m ()
forall (m :: * -> *) a.
PrimMonad m =>
MutVar (PrimState m) a -> (a -> a) -> m ()
modifyMutVar' MutVar s (Seq a)
MutVar (PrimState m) (Seq a)
v (\case Seq a
Empty -> Seq a
forall a. Seq a
Empty; Seq a
as :|> a
_ -> Seq a
as)
peekMutVar :: (MonadPrim s m) => MutVar s (Seq a) -> m (Maybe a)
peekMutVar :: forall s (m :: * -> *) a.
MonadPrim s m =>
MutVar s (Seq a) -> m (Maybe a)
peekMutVar = (Seq a -> Maybe a) -> m (Seq a) -> m (Maybe a)
forall a b. (a -> b) -> m a -> m b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\case Seq a
Empty -> Maybe a
forall a. Maybe a
Nothing; Seq a
_ :|> a
a -> a -> Maybe a
forall a. a -> Maybe a
Just a
a) (m (Seq a) -> m (Maybe a))
-> (MutVar s (Seq a) -> m (Seq a))
-> MutVar s (Seq a)
-> m (Maybe a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MutVar s (Seq a) -> m (Seq a)
MutVar (PrimState m) (Seq a) -> m (Seq a)
forall (m :: * -> *) a.
PrimMonad m =>
MutVar (PrimState m) a -> m a
readMutVar
runGetIncM :: (MonadPrim s m) => GetIncM s r m a -> GetIncEnv s r -> GetIncCbChunk r m -> m (Either GetError a)
runGetIncM :: forall s (m :: * -> *) r a.
MonadPrim s m =>
GetIncM s r m a
-> GetIncEnv s r -> GetIncCbChunk r m -> m (Either GetError a)
runGetIncM GetIncM s r m a
m GetIncEnv s r
env GetIncCbChunk r m
cb =
FT (GetIncSuspendChunk r) m (Either GetError a)
-> forall r.
(Either GetError a -> m r)
-> (forall x. (x -> m r) -> GetIncSuspendChunk r x -> m r) -> m r
forall (f :: * -> *) (m :: * -> *) a.
FT f m a
-> forall r.
(a -> m r) -> (forall x. (x -> m r) -> f x -> m r) -> m r
runFT
(ExceptT GetError (FT (GetIncSuspendChunk r) m) a
-> FT (GetIncSuspendChunk r) m (Either GetError a)
forall e (m :: * -> *) a. ExceptT e m a -> m (Either e a)
runExceptT (ReaderT
(GetIncEnv s r) (ExceptT GetError (FT (GetIncSuspendChunk r) m)) a
-> GetIncEnv s r
-> ExceptT GetError (FT (GetIncSuspendChunk r) m) a
forall r (m :: * -> *) a. ReaderT r m a -> r -> m a
runReaderT (GetIncM s r m a
-> ReaderT
(GetIncEnv s r) (ExceptT GetError (FT (GetIncSuspendChunk r) m)) a
forall s r (m :: * -> *) a.
GetIncM s r m a
-> ReaderT
(GetIncEnv s r) (ExceptT GetError (FT (GetIncSuspendChunk r) m)) a
unGetIncM GetIncM s r m a
m) GetIncEnv s r
env))
Either GetError a -> m (Either GetError a)
forall a. a -> m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure
(\x -> m (Either GetError a)
k2 (GetIncSuspend GetIncRequest
req Maybe (GetIncChunk r) -> x
k1) -> GetIncCbChunk r m
cb GetIncRequest
req m (Maybe (GetIncChunk r))
-> (Maybe (GetIncChunk r) -> m (Either GetError a))
-> m (Either GetError a)
forall a b. m a -> (a -> m b) -> m b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= x -> m (Either GetError a)
k2 (x -> m (Either GetError a))
-> (Maybe (GetIncChunk r) -> x)
-> Maybe (GetIncChunk r)
-> m (Either GetError a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Maybe (GetIncChunk r) -> x
k1)
guardReadBytes :: (MonadPrim s m) => Text -> ByteCount -> GetIncM s r m (ByteCount, GetIncChunk r, ByteCount)
guardReadBytes :: forall s (m :: * -> *) r.
MonadPrim s m =>
Text
-> ByteCount -> GetIncM s r m (ByteCount, GetIncChunk r, ByteCount)
guardReadBytes Text
nm ByteCount
bc = do
GetIncEnv MutVar s ByteCount
gloAbsRef MutVar s ByteCount
gloRelRef MutVar s (Seq ByteCount)
capStackRef MutVar s (GetIncChunk r)
chunkRef MutVar s (Seq ByteCount)
lookStackRef <- ReaderT
(GetIncEnv s r)
(ExceptT GetError (FT (GetIncSuspendChunk r) m))
(GetIncEnv s r)
-> GetIncM s r m (GetIncEnv s r)
forall s r (m :: * -> *) a.
ReaderT
(GetIncEnv s r) (ExceptT GetError (FT (GetIncSuspendChunk r) m)) a
-> GetIncM s r m a
GetIncM ReaderT
(GetIncEnv s r)
(ExceptT GetError (FT (GetIncSuspendChunk r) m))
(GetIncEnv s r)
forall r (m :: * -> *). MonadReader r m => m r
ask
ByteCount
gloAbsStart <- m ByteCount -> GetIncM s r m ByteCount
forall (m :: * -> *) a. Monad m => m a -> GetIncM s r m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (MutVar (PrimState m) ByteCount -> m ByteCount
forall (m :: * -> *) a.
PrimMonad m =>
MutVar (PrimState m) a -> m a
readMutVar MutVar s ByteCount
MutVar (PrimState m) ByteCount
gloAbsRef)
let gloAbsEnd :: ByteCount
gloAbsEnd = ByteCount
gloAbsStart ByteCount -> ByteCount -> ByteCount
forall a. Num a => a -> a -> a
+ ByteCount
bc
Maybe ByteCount
mayCap <- m (Maybe ByteCount) -> GetIncM s r m (Maybe ByteCount)
forall (m :: * -> *) a. Monad m => m a -> GetIncM s r m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (MutVar s (Seq ByteCount) -> m (Maybe ByteCount)
forall s (m :: * -> *) a.
MonadPrim s m =>
MutVar s (Seq a) -> m (Maybe a)
peekMutVar MutVar s (Seq ByteCount)
capStackRef)
case Maybe ByteCount
mayCap of
Just ByteCount
cap | ByteCount
gloAbsEnd ByteCount -> ByteCount -> Bool
forall a. Ord a => a -> a -> Bool
> ByteCount
cap -> GetError -> GetIncM s r m ()
forall a. GetError -> GetIncM s r m a
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError (Text -> ByteCount -> ByteCount -> GetError
GetErrorGlobalCap Text
nm ByteCount
cap ByteCount
gloAbsEnd)
Maybe ByteCount
_ -> () -> GetIncM s r m ()
forall a. a -> GetIncM s r m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ()
ByteCount
gloRel <- m ByteCount -> GetIncM s r m ByteCount
forall (m :: * -> *) a. Monad m => m a -> GetIncM s r m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (MutVar (PrimState m) ByteCount -> m ByteCount
forall (m :: * -> *) a.
PrimMonad m =>
MutVar (PrimState m) a -> m a
readMutVar MutVar s ByteCount
MutVar (PrimState m) ByteCount
gloRelRef)
oldChunk :: GetIncChunk r
oldChunk@(GetIncChunk ByteCount
oldOff ByteCount
oldCap r
_) <- m (GetIncChunk r) -> GetIncM s r m (GetIncChunk r)
forall (m :: * -> *) a. Monad m => m a -> GetIncM s r m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (MutVar (PrimState m) (GetIncChunk r) -> m (GetIncChunk r)
forall (m :: * -> *) a.
PrimMonad m =>
MutVar (PrimState m) a -> m a
readMutVar MutVar s (GetIncChunk r)
MutVar (PrimState m) (GetIncChunk r)
chunkRef)
let oldLocOffStart :: ByteCount
oldLocOffStart = ByteCount
gloAbsStart ByteCount -> ByteCount -> ByteCount
forall a. Num a => a -> a -> a
- ByteCount
gloRel ByteCount -> ByteCount -> ByteCount
forall a. Num a => a -> a -> a
+ ByteCount
oldOff
oldLocOffEnd :: ByteCount
oldLocOffEnd = ByteCount
oldLocOffStart ByteCount -> ByteCount -> ByteCount
forall a. Num a => a -> a -> a
+ ByteCount
bc
(GetIncChunk r
newChunk, ByteCount
newLocOffStart) <-
if ByteCount
oldLocOffEnd ByteCount -> ByteCount -> Bool
forall a. Ord a => a -> a -> Bool
<= ByteCount
oldCap
then (GetIncChunk r, ByteCount)
-> GetIncM s r m (GetIncChunk r, ByteCount)
forall a. a -> GetIncM s r m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (GetIncChunk r
oldChunk, ByteCount
oldLocOffStart)
else do
Seq ByteCount
lookStack <- m (Seq ByteCount) -> GetIncM s r m (Seq ByteCount)
forall (m :: * -> *) a. Monad m => m a -> GetIncM s r m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (MutVar (PrimState m) (Seq ByteCount) -> m (Seq ByteCount)
forall (m :: * -> *) a.
PrimMonad m =>
MutVar (PrimState m) a -> m a
readMutVar MutVar s (Seq ByteCount)
MutVar (PrimState m) (Seq ByteCount)
lookStackRef)
let gloBaseStart :: ByteCount
gloBaseStart = case Seq ByteCount
lookStack of Seq ByteCount
Empty -> ByteCount
gloAbsStart; ByteCount
x :<| Seq ByteCount
_ -> ByteCount
x
baseOffStart :: ByteCount
baseOffStart = ByteCount
gloBaseStart ByteCount -> ByteCount -> ByteCount
forall a. Num a => a -> a -> a
- ByteCount
gloRel ByteCount -> ByteCount -> ByteCount
forall a. Num a => a -> a -> a
+ ByteCount
oldOff
baseOffEnd :: ByteCount
baseOffEnd = ByteCount
gloAbsStart ByteCount -> ByteCount -> ByteCount
forall a. Num a => a -> a -> a
- ByteCount
gloRel ByteCount -> ByteCount -> ByteCount
forall a. Num a => a -> a -> a
+ ByteCount
oldOff ByteCount -> ByteCount -> ByteCount
forall a. Num a => a -> a -> a
+ ByteCount
bc
let needLength :: ByteCount
needLength = ByteCount
baseOffEnd ByteCount -> ByteCount -> ByteCount
forall a. Num a => a -> a -> a
- ByteCount
baseOffStart
req :: GetIncRequest
req = ByteCount -> ByteCount -> ByteCount -> GetIncRequest
GetIncRequest ByteCount
gloAbsStart ByteCount
baseOffStart ByteCount
needLength
GetIncSuspend
(GetIncChunk r) (GetIncM s r m (GetIncChunk r, ByteCount))
-> GetIncM s r m (GetIncChunk r, ByteCount)
forall a.
GetIncSuspend (GetIncChunk r) (GetIncM s r m a) -> GetIncM s r m a
forall (f :: * -> *) (m :: * -> *) a.
MonadFree f m =>
f (m a) -> m a
wrap (GetIncSuspend
(GetIncChunk r) (GetIncM s r m (GetIncChunk r, ByteCount))
-> GetIncM s r m (GetIncChunk r, ByteCount))
-> GetIncSuspend
(GetIncChunk r) (GetIncM s r m (GetIncChunk r, ByteCount))
-> GetIncM s r m (GetIncChunk r, ByteCount)
forall a b. (a -> b) -> a -> b
$ GetIncRequest
-> (Maybe (GetIncChunk r)
-> GetIncM s r m (GetIncChunk r, ByteCount))
-> GetIncSuspend
(GetIncChunk r) (GetIncM s r m (GetIncChunk r, ByteCount))
forall z x. GetIncRequest -> (Maybe z -> x) -> GetIncSuspend z x
GetIncSuspend GetIncRequest
req ((Maybe (GetIncChunk r)
-> GetIncM s r m (GetIncChunk r, ByteCount))
-> GetIncSuspend
(GetIncChunk r) (GetIncM s r m (GetIncChunk r, ByteCount)))
-> (Maybe (GetIncChunk r)
-> GetIncM s r m (GetIncChunk r, ByteCount))
-> GetIncSuspend
(GetIncChunk r) (GetIncM s r m (GetIncChunk r, ByteCount))
forall a b. (a -> b) -> a -> b
$ \case
Maybe (GetIncChunk r)
Nothing -> GetError -> GetIncM s r m (GetIncChunk r, ByteCount)
forall a. GetError -> GetIncM s r m a
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError (Text -> ByteCount -> ByteCount -> GetError
GetErrorLocalCap Text
nm ByteCount
oldCap ByteCount
baseOffEnd)
Just newChunk :: GetIncChunk r
newChunk@(GetIncChunk ByteCount
newOff ByteCount
newCap r
_) -> do
let newEnd :: ByteCount
newEnd = ByteCount
newOff ByteCount -> ByteCount -> ByteCount
forall a. Num a => a -> a -> a
+ ByteCount
needLength
Bool -> GetIncM s r m () -> GetIncM s r m ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (ByteCount
newEnd ByteCount -> ByteCount -> Bool
forall a. Ord a => a -> a -> Bool
<= ByteCount
newCap) (GetError -> GetIncM s r m ()
forall a. GetError -> GetIncM s r m a
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError (Text -> ByteCount -> ByteCount -> GetError
GetErrorLocalCap Text
nm ByteCount
newCap ByteCount
newOff))
m () -> GetIncM s r m ()
forall (m :: * -> *) a. Monad m => m a -> GetIncM s r m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (MutVar (PrimState m) (GetIncChunk r) -> GetIncChunk r -> m ()
forall (m :: * -> *) a.
PrimMonad m =>
MutVar (PrimState m) a -> a -> m ()
writeMutVar MutVar s (GetIncChunk r)
MutVar (PrimState m) (GetIncChunk r)
chunkRef GetIncChunk r
newChunk)
m () -> GetIncM s r m ()
forall (m :: * -> *) a. Monad m => m a -> GetIncM s r m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (MutVar (PrimState m) ByteCount -> ByteCount -> m ()
forall (m :: * -> *) a.
PrimMonad m =>
MutVar (PrimState m) a -> a -> m ()
writeMutVar MutVar s ByteCount
MutVar (PrimState m) ByteCount
gloRelRef ByteCount
gloBaseStart)
(GetIncChunk r, ByteCount)
-> GetIncM s r m (GetIncChunk r, ByteCount)
forall a. a -> GetIncM s r m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (GetIncChunk r
newChunk, GetIncChunk r -> ByteCount
forall r. GetIncChunk r -> ByteCount
gicLocalOff GetIncChunk r
newChunk)
(ByteCount, GetIncChunk r, ByteCount)
-> GetIncM s r m (ByteCount, GetIncChunk r, ByteCount)
forall a. a -> GetIncM s r m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (ByteCount
gloAbsEnd, GetIncChunk r
newChunk, ByteCount
newLocOffStart)
readBytes :: (MonadPrim s m) => Text -> ByteCount -> (r -> ByteCount -> m a) -> GetIncM s r m a
readBytes :: forall s (m :: * -> *) r a.
MonadPrim s m =>
Text -> ByteCount -> (r -> ByteCount -> m a) -> GetIncM s r m a
readBytes Text
nm ByteCount
bc r -> ByteCount -> m a
f = do
(ByteCount
gloAbsEnd, GetIncChunk r
newChunk, ByteCount
newLocOffStart) <- Text
-> ByteCount -> GetIncM s r m (ByteCount, GetIncChunk r, ByteCount)
forall s (m :: * -> *) r.
MonadPrim s m =>
Text
-> ByteCount -> GetIncM s r m (ByteCount, GetIncChunk r, ByteCount)
guardReadBytes Text
nm ByteCount
bc
let mem :: r
mem = GetIncChunk r -> r
forall r. GetIncChunk r -> r
gicArray GetIncChunk r
newChunk
a
a <- m a -> GetIncM s r m a
forall (m :: * -> *) a. Monad m => m a -> GetIncM s r m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (r -> ByteCount -> m a
f r
mem ByteCount
newLocOffStart)
MutVar s ByteCount
gloAbsRef <- ReaderT
(GetIncEnv s r)
(ExceptT GetError (FT (GetIncSuspendChunk r) m))
(MutVar s ByteCount)
-> GetIncM s r m (MutVar s ByteCount)
forall s r (m :: * -> *) a.
ReaderT
(GetIncEnv s r) (ExceptT GetError (FT (GetIncSuspendChunk r) m)) a
-> GetIncM s r m a
GetIncM ((GetIncEnv s r -> MutVar s ByteCount)
-> ReaderT
(GetIncEnv s r)
(ExceptT GetError (FT (GetIncSuspendChunk r) m))
(MutVar s ByteCount)
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks GetIncEnv s r -> MutVar s ByteCount
forall s r. GetIncEnv s r -> MutVar s ByteCount
gieGlobalAbs)
m () -> GetIncM s r m ()
forall (m :: * -> *) a. Monad m => m a -> GetIncM s r m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (MutVar (PrimState m) ByteCount -> ByteCount -> m ()
forall (m :: * -> *) a.
PrimMonad m =>
MutVar (PrimState m) a -> a -> m ()
writeMutVar MutVar s ByteCount
MutVar (PrimState m) ByteCount
gloAbsRef ByteCount
gloAbsEnd)
a -> GetIncM s r m a
forall a. a -> GetIncM s r m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure a
a
readScope :: (MonadPrim s m, ReadMem r m) => GetScopeF (GetIncM s r m a) -> GetIncM s r m a
readScope :: forall s (m :: * -> *) r a.
(MonadPrim s m, ReadMem r m) =>
GetScopeF (GetIncM s r m a) -> GetIncM s r m a
readScope (GetScopeF ScopeMode
sm ByteCount
bc Get z
g z -> GetIncM s r m a
k) = do
GetIncEnv MutVar s ByteCount
gloAbsRef MutVar s ByteCount
_ MutVar s (Seq ByteCount)
capStackRef MutVar s (GetIncChunk r)
_ MutVar s (Seq ByteCount)
_ <- ReaderT
(GetIncEnv s r)
(ExceptT GetError (FT (GetIncSuspendChunk r) m))
(GetIncEnv s r)
-> GetIncM s r m (GetIncEnv s r)
forall s r (m :: * -> *) a.
ReaderT
(GetIncEnv s r) (ExceptT GetError (FT (GetIncSuspendChunk r) m)) a
-> GetIncM s r m a
GetIncM ReaderT
(GetIncEnv s r)
(ExceptT GetError (FT (GetIncSuspendChunk r) m))
(GetIncEnv s r)
forall r (m :: * -> *). MonadReader r m => m r
ask
ByteCount
gloAbsStart <- m ByteCount -> GetIncM s r m ByteCount
forall (m :: * -> *) a. Monad m => m a -> GetIncM s r m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (MutVar (PrimState m) ByteCount -> m ByteCount
forall (m :: * -> *) a.
PrimMonad m =>
MutVar (PrimState m) a -> m a
readMutVar MutVar s ByteCount
MutVar (PrimState m) ByteCount
gloAbsRef)
let gloAbsMax :: ByteCount
gloAbsMax = ByteCount
gloAbsStart ByteCount -> ByteCount -> ByteCount
forall a. Num a => a -> a -> a
+ ByteCount
bc
Maybe ByteCount
mayCap <- m (Maybe ByteCount) -> GetIncM s r m (Maybe ByteCount)
forall (m :: * -> *) a. Monad m => m a -> GetIncM s r m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (MutVar s (Seq ByteCount) -> m (Maybe ByteCount)
forall s (m :: * -> *) a.
MonadPrim s m =>
MutVar s (Seq a) -> m (Maybe a)
peekMutVar MutVar s (Seq ByteCount)
capStackRef)
case Maybe ByteCount
mayCap of
Just ByteCount
cap
| ScopeMode
sm ScopeMode -> ScopeMode -> Bool
forall a. Eq a => a -> a -> Bool
== ScopeMode
ScopeModeExact Bool -> Bool -> Bool
&& ByteCount
gloAbsMax ByteCount -> ByteCount -> Bool
forall a. Ord a => a -> a -> Bool
> ByteCount
cap ->
GetError -> GetIncM s r m ()
forall a. GetError -> GetIncM s r m a
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError (Text -> ByteCount -> ByteCount -> GetError
GetErrorGlobalCap Text
"scope" ByteCount
cap ByteCount
gloAbsMax)
Maybe ByteCount
_ -> () -> GetIncM s r m ()
forall a. a -> GetIncM s r m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ()
m () -> GetIncM s r m ()
forall (m :: * -> *) a. Monad m => m a -> GetIncM s r m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (MutVar s (Seq ByteCount) -> ByteCount -> m ()
forall s (m :: * -> *) a.
MonadPrim s m =>
MutVar s (Seq a) -> a -> m ()
pushMutVar MutVar s (Seq ByteCount)
capStackRef ByteCount
gloAbsMax)
z
a <- Get z -> GetIncM s r m z
forall s (m :: * -> *) r a.
(MonadPrim s m, ReadMem r m) =>
Get a -> GetIncM s r m a
interpGetInc Get z
g
m () -> GetIncM s r m ()
forall (m :: * -> *) a. Monad m => m a -> GetIncM s r m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (MutVar s (Seq ByteCount) -> m ()
forall s (m :: * -> *) a. MonadPrim s m => MutVar s (Seq a) -> m ()
popMutVar MutVar s (Seq ByteCount)
capStackRef)
ByteCount
gloAbsEnd <- m ByteCount -> GetIncM s r m ByteCount
forall (m :: * -> *) a. Monad m => m a -> GetIncM s r m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (MutVar (PrimState m) ByteCount -> m ByteCount
forall (m :: * -> *) a.
PrimMonad m =>
MutVar (PrimState m) a -> m a
readMutVar MutVar s ByteCount
MutVar (PrimState m) ByteCount
gloAbsRef)
let actualBc :: ByteCount
actualBc = ByteCount
gloAbsEnd ByteCount -> ByteCount -> ByteCount
forall a. Num a => a -> a -> a
- ByteCount
gloAbsStart
if (ScopeMode
sm ScopeMode -> ScopeMode -> Bool
forall a. Eq a => a -> a -> Bool
== ScopeMode
ScopeModeExact Bool -> Bool -> Bool
&& ByteCount
actualBc ByteCount -> ByteCount -> Bool
forall a. Eq a => a -> a -> Bool
== ByteCount
bc) Bool -> Bool -> Bool
|| (ScopeMode
sm ScopeMode -> ScopeMode -> Bool
forall a. Eq a => a -> a -> Bool
== ScopeMode
ScopeModeWithin Bool -> Bool -> Bool
&& ByteCount
actualBc ByteCount -> ByteCount -> Bool
forall a. Ord a => a -> a -> Bool
<= ByteCount
bc)
then z -> GetIncM s r m a
k z
a
else GetError -> GetIncM s r m a
forall a. GetError -> GetIncM s r m a
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError (ScopeMode -> ByteCount -> ByteCount -> GetError
GetErrorScopedMismatch ScopeMode
sm ByteCount
actualBc ByteCount
bc)
readStaticSeq :: (MonadPrim s m, ReadMem r m) => GetStaticSeqF (GetIncM s r m a) -> GetIncM s r m a
readStaticSeq :: forall s (m :: * -> *) r a.
(MonadPrim s m, ReadMem r m) =>
GetStaticSeqF (GetIncM s r m a) -> GetIncM s r m a
readStaticSeq gss :: GetStaticSeqF (GetIncM s r m a)
gss@(GetStaticSeqF ElemCount
ec Get z
g Seq z -> GetIncM s r m a
k) = do
let bc :: ByteCount
bc = GetStaticSeqF (GetIncM s r m a) -> ByteCount
forall a. GetStaticSeqF a -> ByteCount
getStaticSeqSize GetStaticSeqF (GetIncM s r m a)
gss
(ByteCount, GetIncChunk r, ByteCount)
_ <- Text
-> ByteCount -> GetIncM s r m (ByteCount, GetIncChunk r, ByteCount)
forall s (m :: * -> *) r.
MonadPrim s m =>
Text
-> ByteCount -> GetIncM s r m (ByteCount, GetIncChunk r, ByteCount)
guardReadBytes Text
"static sequence" ByteCount
bc
Seq z
ss <- Int -> GetIncM s r m z -> GetIncM s r m (Seq z)
forall (f :: * -> *) a. Applicative f => Int -> f a -> f (Seq a)
Seq.replicateA (ElemCount -> Int
forall a b. Coercible a b => a -> b
coerce ElemCount
ec) (Get z -> GetIncM s r m z
forall s (m :: * -> *) r a.
(MonadPrim s m, ReadMem r m) =>
Get a -> GetIncM s r m a
interpGetInc Get z
g)
Seq z -> GetIncM s r m a
k Seq z
ss
readStaticArray :: (MonadPrim s m, ReadMem r m) => GetStaticArrayF (GetIncM s r m a) -> GetIncM s r m a
readStaticArray :: forall s (m :: * -> *) r a.
(MonadPrim s m, ReadMem r m) =>
GetStaticArrayF (GetIncM s r m a) -> GetIncM s r m a
readStaticArray gsa :: GetStaticArrayF (GetIncM s r m a)
gsa@(GetStaticArrayF ElemCount
_ Proxy z
_ PrimArray z -> GetIncM s r m a
k) = do
let bc :: ByteCount
bc = GetStaticArrayF (GetIncM s r m a) -> ByteCount
forall a. GetStaticArrayF a -> ByteCount
getStaticArraySize GetStaticArrayF (GetIncM s r m a)
gsa
ByteArray ByteArray#
ba <- Text
-> ByteCount
-> (r -> ByteCount -> m ByteArray)
-> GetIncM s r m ByteArray
forall s (m :: * -> *) r a.
MonadPrim s m =>
Text -> ByteCount -> (r -> ByteCount -> m a) -> GetIncM s r m a
readBytes Text
"static vector" ByteCount
bc (\r
mem ByteCount
off -> r -> ByteCount -> ByteCount -> m ByteArray
forall r (m :: * -> *).
ReadMem r m =>
r -> ByteCount -> ByteCount -> m ByteArray
cloneArrayMemInBytes r
mem ByteCount
off ByteCount
bc)
PrimArray z -> GetIncM s r m a
k (ByteArray# -> PrimArray z
forall a. ByteArray# -> PrimArray a
PrimArray ByteArray#
ba)
readLookAhead :: (MonadPrim s m, ReadMem r m) => GetLookAheadF (GetIncM s r m a) -> GetIncM s r m a
readLookAhead :: forall s (m :: * -> *) r a.
(MonadPrim s m, ReadMem r m) =>
GetLookAheadF (GetIncM s r m a) -> GetIncM s r m a
readLookAhead (GetLookAheadF Get z
g z -> GetIncM s r m a
k) = do
GetIncEnv MutVar s ByteCount
gloAbsRef MutVar s ByteCount
_ MutVar s (Seq ByteCount)
_ MutVar s (GetIncChunk r)
_ MutVar s (Seq ByteCount)
lookStackRef <- ReaderT
(GetIncEnv s r)
(ExceptT GetError (FT (GetIncSuspendChunk r) m))
(GetIncEnv s r)
-> GetIncM s r m (GetIncEnv s r)
forall s r (m :: * -> *) a.
ReaderT
(GetIncEnv s r) (ExceptT GetError (FT (GetIncSuspendChunk r) m)) a
-> GetIncM s r m a
GetIncM ReaderT
(GetIncEnv s r)
(ExceptT GetError (FT (GetIncSuspendChunk r) m))
(GetIncEnv s r)
forall r (m :: * -> *). MonadReader r m => m r
ask
ByteCount
gloAbs <- m ByteCount -> GetIncM s r m ByteCount
forall (m :: * -> *) a. Monad m => m a -> GetIncM s r m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (MutVar (PrimState m) ByteCount -> m ByteCount
forall (m :: * -> *) a.
PrimMonad m =>
MutVar (PrimState m) a -> m a
readMutVar MutVar s ByteCount
MutVar (PrimState m) ByteCount
gloAbsRef)
m () -> GetIncM s r m ()
forall (m :: * -> *) a. Monad m => m a -> GetIncM s r m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (MutVar s (Seq ByteCount) -> ByteCount -> m ()
forall s (m :: * -> *) a.
MonadPrim s m =>
MutVar s (Seq a) -> a -> m ()
pushMutVar MutVar s (Seq ByteCount)
lookStackRef ByteCount
gloAbs)
z
a <- Get z -> GetIncM s r m z
forall s (m :: * -> *) r a.
(MonadPrim s m, ReadMem r m) =>
Get a -> GetIncM s r m a
interpGetInc Get z
g
m () -> GetIncM s r m ()
forall (m :: * -> *) a. Monad m => m a -> GetIncM s r m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (MutVar s (Seq ByteCount) -> m ()
forall s (m :: * -> *) a. MonadPrim s m => MutVar s (Seq a) -> m ()
popMutVar MutVar s (Seq ByteCount)
lookStackRef)
m () -> GetIncM s r m ()
forall (m :: * -> *) a. Monad m => m a -> GetIncM s r m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (MutVar (PrimState m) ByteCount -> ByteCount -> m ()
forall (m :: * -> *) a.
PrimMonad m =>
MutVar (PrimState m) a -> a -> m ()
writeMutVar MutVar s ByteCount
MutVar (PrimState m) ByteCount
gloAbsRef ByteCount
gloAbs)
z -> GetIncM s r m a
k z
a
interpGetInc :: (MonadPrim s m, ReadMem r m) => Get a -> GetIncM s r m a
interpGetInc :: forall s (m :: * -> *) r a.
(MonadPrim s m, ReadMem r m) =>
Get a -> GetIncM s r m a
interpGetInc (Get F GetF a
g) = ((GetF (GetIncM s r m a) -> GetIncM s r m a)
-> F GetF a -> GetIncM s r m a)
-> F GetF a
-> (GetF (GetIncM s r m a) -> GetIncM s r m a)
-> GetIncM s r m a
forall a b c. (a -> b -> c) -> b -> a -> c
flip (GetF (GetIncM s r m a) -> GetIncM s r m a)
-> F GetF a -> GetIncM s r m a
forall (m :: * -> *) (f :: * -> *) a.
Monad m =>
(f (m a) -> m a) -> F f a -> m a
iterM F GetF a
g ((GetF (GetIncM s r m a) -> GetIncM s r m a) -> GetIncM s r m a)
-> (GetF (GetIncM s r m a) -> GetIncM s r m a) -> GetIncM s r m a
forall a b. (a -> b) -> a -> b
$ \case
GetFWord8 Word8 -> GetIncM s r m a
k -> Text
-> ByteCount -> (r -> ByteCount -> m Word8) -> GetIncM s r m Word8
forall s (m :: * -> *) r a.
MonadPrim s m =>
Text -> ByteCount -> (r -> ByteCount -> m a) -> GetIncM s r m a
readBytes Text
"Word8" ByteCount
1 (forall r (m :: * -> *) a.
(ReadMem r m, Prim a, PrimUnaligned a) =>
r -> ByteCount -> m a
indexMemInBytes @_ @_ @Word8) GetIncM s r m Word8
-> (Word8 -> GetIncM s r m a) -> GetIncM s r m a
forall a b.
GetIncM s r m a -> (a -> GetIncM s r m b) -> GetIncM s r m b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Word8 -> GetIncM s r m a
k
GetFInt8 Int8 -> GetIncM s r m a
k -> Text
-> ByteCount -> (r -> ByteCount -> m Int8) -> GetIncM s r m Int8
forall s (m :: * -> *) r a.
MonadPrim s m =>
Text -> ByteCount -> (r -> ByteCount -> m a) -> GetIncM s r m a
readBytes Text
"Int8" ByteCount
1 (forall r (m :: * -> *) a.
(ReadMem r m, Prim a, PrimUnaligned a) =>
r -> ByteCount -> m a
indexMemInBytes @_ @_ @Int8) GetIncM s r m Int8 -> (Int8 -> GetIncM s r m a) -> GetIncM s r m a
forall a b.
GetIncM s r m a -> (a -> GetIncM s r m b) -> GetIncM s r m b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Int8 -> GetIncM s r m a
k
GetFWord16LE Word16LE -> GetIncM s r m a
k -> Text
-> ByteCount
-> (r -> ByteCount -> m Word16LE)
-> GetIncM s r m Word16LE
forall s (m :: * -> *) r a.
MonadPrim s m =>
Text -> ByteCount -> (r -> ByteCount -> m a) -> GetIncM s r m a
readBytes Text
"Word16LE" ByteCount
2 (forall r (m :: * -> *) a.
(ReadMem r m, Prim a, PrimUnaligned a) =>
r -> ByteCount -> m a
indexMemInBytes @_ @_ @Word16LE) GetIncM s r m Word16LE
-> (Word16LE -> GetIncM s r m a) -> GetIncM s r m a
forall a b.
GetIncM s r m a -> (a -> GetIncM s r m b) -> GetIncM s r m b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Word16LE -> GetIncM s r m a
k
GetFInt16LE Int16LE -> GetIncM s r m a
k -> Text
-> ByteCount
-> (r -> ByteCount -> m Int16LE)
-> GetIncM s r m Int16LE
forall s (m :: * -> *) r a.
MonadPrim s m =>
Text -> ByteCount -> (r -> ByteCount -> m a) -> GetIncM s r m a
readBytes Text
"Int16LE" ByteCount
2 (forall r (m :: * -> *) a.
(ReadMem r m, Prim a, PrimUnaligned a) =>
r -> ByteCount -> m a
indexMemInBytes @_ @_ @Int16LE) GetIncM s r m Int16LE
-> (Int16LE -> GetIncM s r m a) -> GetIncM s r m a
forall a b.
GetIncM s r m a -> (a -> GetIncM s r m b) -> GetIncM s r m b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Int16LE -> GetIncM s r m a
k
GetFWord24LE Word24LE -> GetIncM s r m a
k -> Text
-> ByteCount
-> (r -> ByteCount -> m Word24LE)
-> GetIncM s r m Word24LE
forall s (m :: * -> *) r a.
MonadPrim s m =>
Text -> ByteCount -> (r -> ByteCount -> m a) -> GetIncM s r m a
readBytes Text
"Word24LE" ByteCount
3 (forall r (m :: * -> *) a.
(ReadMem r m, Prim a, PrimUnaligned a) =>
r -> ByteCount -> m a
indexMemInBytes @_ @_ @Word24LE) GetIncM s r m Word24LE
-> (Word24LE -> GetIncM s r m a) -> GetIncM s r m a
forall a b.
GetIncM s r m a -> (a -> GetIncM s r m b) -> GetIncM s r m b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Word24LE -> GetIncM s r m a
k
GetFInt24LE Int24LE -> GetIncM s r m a
k -> Text
-> ByteCount
-> (r -> ByteCount -> m Int24LE)
-> GetIncM s r m Int24LE
forall s (m :: * -> *) r a.
MonadPrim s m =>
Text -> ByteCount -> (r -> ByteCount -> m a) -> GetIncM s r m a
readBytes Text
"Int24LE" ByteCount
3 (forall r (m :: * -> *) a.
(ReadMem r m, Prim a, PrimUnaligned a) =>
r -> ByteCount -> m a
indexMemInBytes @_ @_ @Int24LE) GetIncM s r m Int24LE
-> (Int24LE -> GetIncM s r m a) -> GetIncM s r m a
forall a b.
GetIncM s r m a -> (a -> GetIncM s r m b) -> GetIncM s r m b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Int24LE -> GetIncM s r m a
k
GetFWord32LE Word32LE -> GetIncM s r m a
k -> Text
-> ByteCount
-> (r -> ByteCount -> m Word32LE)
-> GetIncM s r m Word32LE
forall s (m :: * -> *) r a.
MonadPrim s m =>
Text -> ByteCount -> (r -> ByteCount -> m a) -> GetIncM s r m a
readBytes Text
"Word32LE" ByteCount
4 (forall r (m :: * -> *) a.
(ReadMem r m, Prim a, PrimUnaligned a) =>
r -> ByteCount -> m a
indexMemInBytes @_ @_ @Word32LE) GetIncM s r m Word32LE
-> (Word32LE -> GetIncM s r m a) -> GetIncM s r m a
forall a b.
GetIncM s r m a -> (a -> GetIncM s r m b) -> GetIncM s r m b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Word32LE -> GetIncM s r m a
k
GetFInt32LE Int32LE -> GetIncM s r m a
k -> Text
-> ByteCount
-> (r -> ByteCount -> m Int32LE)
-> GetIncM s r m Int32LE
forall s (m :: * -> *) r a.
MonadPrim s m =>
Text -> ByteCount -> (r -> ByteCount -> m a) -> GetIncM s r m a
readBytes Text
"Int32LE" ByteCount
4 (forall r (m :: * -> *) a.
(ReadMem r m, Prim a, PrimUnaligned a) =>
r -> ByteCount -> m a
indexMemInBytes @_ @_ @Int32LE) GetIncM s r m Int32LE
-> (Int32LE -> GetIncM s r m a) -> GetIncM s r m a
forall a b.
GetIncM s r m a -> (a -> GetIncM s r m b) -> GetIncM s r m b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Int32LE -> GetIncM s r m a
k
GetFWord64LE Word64LE -> GetIncM s r m a
k -> Text
-> ByteCount
-> (r -> ByteCount -> m Word64LE)
-> GetIncM s r m Word64LE
forall s (m :: * -> *) r a.
MonadPrim s m =>
Text -> ByteCount -> (r -> ByteCount -> m a) -> GetIncM s r m a
readBytes Text
"Word64LE" ByteCount
8 (forall r (m :: * -> *) a.
(ReadMem r m, Prim a, PrimUnaligned a) =>
r -> ByteCount -> m a
indexMemInBytes @_ @_ @Word64LE) GetIncM s r m Word64LE
-> (Word64LE -> GetIncM s r m a) -> GetIncM s r m a
forall a b.
GetIncM s r m a -> (a -> GetIncM s r m b) -> GetIncM s r m b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Word64LE -> GetIncM s r m a
k
GetFInt64LE Int64LE -> GetIncM s r m a
k -> Text
-> ByteCount
-> (r -> ByteCount -> m Int64LE)
-> GetIncM s r m Int64LE
forall s (m :: * -> *) r a.
MonadPrim s m =>
Text -> ByteCount -> (r -> ByteCount -> m a) -> GetIncM s r m a
readBytes Text
"Int64LE" ByteCount
8 (forall r (m :: * -> *) a.
(ReadMem r m, Prim a, PrimUnaligned a) =>
r -> ByteCount -> m a
indexMemInBytes @_ @_ @Int64LE) GetIncM s r m Int64LE
-> (Int64LE -> GetIncM s r m a) -> GetIncM s r m a
forall a b.
GetIncM s r m a -> (a -> GetIncM s r m b) -> GetIncM s r m b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Int64LE -> GetIncM s r m a
k
GetFFloatLE FloatLE -> GetIncM s r m a
k -> Text
-> ByteCount
-> (r -> ByteCount -> m FloatLE)
-> GetIncM s r m FloatLE
forall s (m :: * -> *) r a.
MonadPrim s m =>
Text -> ByteCount -> (r -> ByteCount -> m a) -> GetIncM s r m a
readBytes Text
"FloatLE" ByteCount
4 (forall r (m :: * -> *) a.
(ReadMem r m, Prim a, PrimUnaligned a) =>
r -> ByteCount -> m a
indexMemInBytes @_ @_ @FloatLE) GetIncM s r m FloatLE
-> (FloatLE -> GetIncM s r m a) -> GetIncM s r m a
forall a b.
GetIncM s r m a -> (a -> GetIncM s r m b) -> GetIncM s r m b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FloatLE -> GetIncM s r m a
k
GetFDoubleLE DoubleLE -> GetIncM s r m a
k -> Text
-> ByteCount
-> (r -> ByteCount -> m DoubleLE)
-> GetIncM s r m DoubleLE
forall s (m :: * -> *) r a.
MonadPrim s m =>
Text -> ByteCount -> (r -> ByteCount -> m a) -> GetIncM s r m a
readBytes Text
"DoubleLE" ByteCount
8 (forall r (m :: * -> *) a.
(ReadMem r m, Prim a, PrimUnaligned a) =>
r -> ByteCount -> m a
indexMemInBytes @_ @_ @DoubleLE) GetIncM s r m DoubleLE
-> (DoubleLE -> GetIncM s r m a) -> GetIncM s r m a
forall a b.
GetIncM s r m a -> (a -> GetIncM s r m b) -> GetIncM s r m b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= DoubleLE -> GetIncM s r m a
k
GetFWord16BE Word16BE -> GetIncM s r m a
k -> Text
-> ByteCount
-> (r -> ByteCount -> m Word16BE)
-> GetIncM s r m Word16BE
forall s (m :: * -> *) r a.
MonadPrim s m =>
Text -> ByteCount -> (r -> ByteCount -> m a) -> GetIncM s r m a
readBytes Text
"Word16BE" ByteCount
2 (forall r (m :: * -> *) a.
(ReadMem r m, Prim a, PrimUnaligned a) =>
r -> ByteCount -> m a
indexMemInBytes @_ @_ @Word16BE) GetIncM s r m Word16BE
-> (Word16BE -> GetIncM s r m a) -> GetIncM s r m a
forall a b.
GetIncM s r m a -> (a -> GetIncM s r m b) -> GetIncM s r m b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Word16BE -> GetIncM s r m a
k
GetFInt16BE Int16BE -> GetIncM s r m a
k -> Text
-> ByteCount
-> (r -> ByteCount -> m Int16BE)
-> GetIncM s r m Int16BE
forall s (m :: * -> *) r a.
MonadPrim s m =>
Text -> ByteCount -> (r -> ByteCount -> m a) -> GetIncM s r m a
readBytes Text
"Int16BE" ByteCount
2 (forall r (m :: * -> *) a.
(ReadMem r m, Prim a, PrimUnaligned a) =>
r -> ByteCount -> m a
indexMemInBytes @_ @_ @Int16BE) GetIncM s r m Int16BE
-> (Int16BE -> GetIncM s r m a) -> GetIncM s r m a
forall a b.
GetIncM s r m a -> (a -> GetIncM s r m b) -> GetIncM s r m b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Int16BE -> GetIncM s r m a
k
GetFWord24BE Word24BE -> GetIncM s r m a
k -> Text
-> ByteCount
-> (r -> ByteCount -> m Word24BE)
-> GetIncM s r m Word24BE
forall s (m :: * -> *) r a.
MonadPrim s m =>
Text -> ByteCount -> (r -> ByteCount -> m a) -> GetIncM s r m a
readBytes Text
"Word24BE" ByteCount
3 (forall r (m :: * -> *) a.
(ReadMem r m, Prim a, PrimUnaligned a) =>
r -> ByteCount -> m a
indexMemInBytes @_ @_ @Word24BE) GetIncM s r m Word24BE
-> (Word24BE -> GetIncM s r m a) -> GetIncM s r m a
forall a b.
GetIncM s r m a -> (a -> GetIncM s r m b) -> GetIncM s r m b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Word24BE -> GetIncM s r m a
k
GetFInt24BE Int24BE -> GetIncM s r m a
k -> Text
-> ByteCount
-> (r -> ByteCount -> m Int24BE)
-> GetIncM s r m Int24BE
forall s (m :: * -> *) r a.
MonadPrim s m =>
Text -> ByteCount -> (r -> ByteCount -> m a) -> GetIncM s r m a
readBytes Text
"Int24BE" ByteCount
3 (forall r (m :: * -> *) a.
(ReadMem r m, Prim a, PrimUnaligned a) =>
r -> ByteCount -> m a
indexMemInBytes @_ @_ @Int24BE) GetIncM s r m Int24BE
-> (Int24BE -> GetIncM s r m a) -> GetIncM s r m a
forall a b.
GetIncM s r m a -> (a -> GetIncM s r m b) -> GetIncM s r m b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Int24BE -> GetIncM s r m a
k
GetFWord32BE Word32BE -> GetIncM s r m a
k -> Text
-> ByteCount
-> (r -> ByteCount -> m Word32BE)
-> GetIncM s r m Word32BE
forall s (m :: * -> *) r a.
MonadPrim s m =>
Text -> ByteCount -> (r -> ByteCount -> m a) -> GetIncM s r m a
readBytes Text
"Word32BE" ByteCount
4 (forall r (m :: * -> *) a.
(ReadMem r m, Prim a, PrimUnaligned a) =>
r -> ByteCount -> m a
indexMemInBytes @_ @_ @Word32BE) GetIncM s r m Word32BE
-> (Word32BE -> GetIncM s r m a) -> GetIncM s r m a
forall a b.
GetIncM s r m a -> (a -> GetIncM s r m b) -> GetIncM s r m b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Word32BE -> GetIncM s r m a
k
GetFInt32BE Int32BE -> GetIncM s r m a
k -> Text
-> ByteCount
-> (r -> ByteCount -> m Int32BE)
-> GetIncM s r m Int32BE
forall s (m :: * -> *) r a.
MonadPrim s m =>
Text -> ByteCount -> (r -> ByteCount -> m a) -> GetIncM s r m a
readBytes Text
"Int32BE" ByteCount
4 (forall r (m :: * -> *) a.
(ReadMem r m, Prim a, PrimUnaligned a) =>
r -> ByteCount -> m a
indexMemInBytes @_ @_ @Int32BE) GetIncM s r m Int32BE
-> (Int32BE -> GetIncM s r m a) -> GetIncM s r m a
forall a b.
GetIncM s r m a -> (a -> GetIncM s r m b) -> GetIncM s r m b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Int32BE -> GetIncM s r m a
k
GetFWord64BE Word64BE -> GetIncM s r m a
k -> Text
-> ByteCount
-> (r -> ByteCount -> m Word64BE)
-> GetIncM s r m Word64BE
forall s (m :: * -> *) r a.
MonadPrim s m =>
Text -> ByteCount -> (r -> ByteCount -> m a) -> GetIncM s r m a
readBytes Text
"Word64BE" ByteCount
8 (forall r (m :: * -> *) a.
(ReadMem r m, Prim a, PrimUnaligned a) =>
r -> ByteCount -> m a
indexMemInBytes @_ @_ @Word64BE) GetIncM s r m Word64BE
-> (Word64BE -> GetIncM s r m a) -> GetIncM s r m a
forall a b.
GetIncM s r m a -> (a -> GetIncM s r m b) -> GetIncM s r m b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Word64BE -> GetIncM s r m a
k
GetFInt64BE Int64BE -> GetIncM s r m a
k -> Text
-> ByteCount
-> (r -> ByteCount -> m Int64BE)
-> GetIncM s r m Int64BE
forall s (m :: * -> *) r a.
MonadPrim s m =>
Text -> ByteCount -> (r -> ByteCount -> m a) -> GetIncM s r m a
readBytes Text
"Int64BE" ByteCount
8 (forall r (m :: * -> *) a.
(ReadMem r m, Prim a, PrimUnaligned a) =>
r -> ByteCount -> m a
indexMemInBytes @_ @_ @Int64BE) GetIncM s r m Int64BE
-> (Int64BE -> GetIncM s r m a) -> GetIncM s r m a
forall a b.
GetIncM s r m a -> (a -> GetIncM s r m b) -> GetIncM s r m b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Int64BE -> GetIncM s r m a
k
GetFFloatBE FloatBE -> GetIncM s r m a
k -> Text
-> ByteCount
-> (r -> ByteCount -> m FloatBE)
-> GetIncM s r m FloatBE
forall s (m :: * -> *) r a.
MonadPrim s m =>
Text -> ByteCount -> (r -> ByteCount -> m a) -> GetIncM s r m a
readBytes Text
"FloatBE" ByteCount
4 (forall r (m :: * -> *) a.
(ReadMem r m, Prim a, PrimUnaligned a) =>
r -> ByteCount -> m a
indexMemInBytes @_ @_ @FloatBE) GetIncM s r m FloatBE
-> (FloatBE -> GetIncM s r m a) -> GetIncM s r m a
forall a b.
GetIncM s r m a -> (a -> GetIncM s r m b) -> GetIncM s r m b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FloatBE -> GetIncM s r m a
k
GetFDoubleBE DoubleBE -> GetIncM s r m a
k -> Text
-> ByteCount
-> (r -> ByteCount -> m DoubleBE)
-> GetIncM s r m DoubleBE
forall s (m :: * -> *) r a.
MonadPrim s m =>
Text -> ByteCount -> (r -> ByteCount -> m a) -> GetIncM s r m a
readBytes Text
"DoubleBE" ByteCount
8 (forall r (m :: * -> *) a.
(ReadMem r m, Prim a, PrimUnaligned a) =>
r -> ByteCount -> m a
indexMemInBytes @_ @_ @DoubleBE) GetIncM s r m DoubleBE
-> (DoubleBE -> GetIncM s r m a) -> GetIncM s r m a
forall a b.
GetIncM s r m a -> (a -> GetIncM s r m b) -> GetIncM s r m b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= DoubleBE -> GetIncM s r m a
k
GetFShortByteString ByteCount
bc ShortByteString -> GetIncM s r m a
k ->
Text
-> ByteCount
-> (r -> ByteCount -> m ShortByteString)
-> GetIncM s r m ShortByteString
forall s (m :: * -> *) r a.
MonadPrim s m =>
Text -> ByteCount -> (r -> ByteCount -> m a) -> GetIncM s r m a
readBytes Text
"ShortByteString" ByteCount
bc (\r
mem ByteCount
off -> r -> ByteCount -> ByteCount -> m ShortByteString
forall r (m :: * -> *).
ReadMem r m =>
r -> ByteCount -> ByteCount -> m ShortByteString
readSBSMem r
mem ByteCount
off ByteCount
bc) GetIncM s r m ShortByteString
-> (ShortByteString -> GetIncM s r m a) -> GetIncM s r m a
forall a b.
GetIncM s r m a -> (a -> GetIncM s r m b) -> GetIncM s r m b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ShortByteString -> GetIncM s r m a
k
GetFStaticSeq GetStaticSeqF (GetIncM s r m a)
gss -> GetStaticSeqF (GetIncM s r m a) -> GetIncM s r m a
forall s (m :: * -> *) r a.
(MonadPrim s m, ReadMem r m) =>
GetStaticSeqF (GetIncM s r m a) -> GetIncM s r m a
readStaticSeq GetStaticSeqF (GetIncM s r m a)
gss
GetFStaticArray GetStaticArrayF (GetIncM s r m a)
gsa -> GetStaticArrayF (GetIncM s r m a) -> GetIncM s r m a
forall s (m :: * -> *) r a.
(MonadPrim s m, ReadMem r m) =>
GetStaticArrayF (GetIncM s r m a) -> GetIncM s r m a
readStaticArray GetStaticArrayF (GetIncM s r m a)
gsa
GetFByteArray ByteCount
bc ByteArray -> GetIncM s r m a
k ->
Text
-> ByteCount
-> (r -> ByteCount -> m ByteArray)
-> GetIncM s r m ByteArray
forall s (m :: * -> *) r a.
MonadPrim s m =>
Text -> ByteCount -> (r -> ByteCount -> m a) -> GetIncM s r m a
readBytes Text
"ByteArray" ByteCount
bc (\r
mem ByteCount
off -> r -> ByteCount -> ByteCount -> m ByteArray
forall r (m :: * -> *).
ReadMem r m =>
r -> ByteCount -> ByteCount -> m ByteArray
cloneArrayMemInBytes r
mem ByteCount
off ByteCount
bc) GetIncM s r m ByteArray
-> (ByteArray -> GetIncM s r m a) -> GetIncM s r m a
forall a b.
GetIncM s r m a -> (a -> GetIncM s r m b) -> GetIncM s r m b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ByteArray -> GetIncM s r m a
k
GetFScope GetScopeF (GetIncM s r m a)
gs -> GetScopeF (GetIncM s r m a) -> GetIncM s r m a
forall s (m :: * -> *) r a.
(MonadPrim s m, ReadMem r m) =>
GetScopeF (GetIncM s r m a) -> GetIncM s r m a
readScope GetScopeF (GetIncM s r m a)
gs
GetFSkip ByteCount
bc GetIncM s r m a
k -> Text -> ByteCount -> (r -> ByteCount -> m ()) -> GetIncM s r m ()
forall s (m :: * -> *) r a.
MonadPrim s m =>
Text -> ByteCount -> (r -> ByteCount -> m a) -> GetIncM s r m a
readBytes Text
"skip" ByteCount
bc (\r
_ ByteCount
_ -> () -> m ()
forall a. a -> m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ()) GetIncM s r m () -> GetIncM s r m a -> GetIncM s r m a
forall a b. GetIncM s r m a -> GetIncM s r m b -> GetIncM s r m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> GetIncM s r m a
k
GetFLookAhead GetLookAheadF (GetIncM s r m a)
gla -> GetLookAheadF (GetIncM s r m a) -> GetIncM s r m a
forall s (m :: * -> *) r a.
(MonadPrim s m, ReadMem r m) =>
GetLookAheadF (GetIncM s r m a) -> GetIncM s r m a
readLookAhead GetLookAheadF (GetIncM s r m a)
gla
GetFRemainingSize ByteCount -> GetIncM s r m a
k -> do
GetIncEnv MutVar s ByteCount
gloAbsRef MutVar s ByteCount
_ MutVar s (Seq ByteCount)
capStackRef MutVar s (GetIncChunk r)
_ MutVar s (Seq ByteCount)
_ <- ReaderT
(GetIncEnv s r)
(ExceptT GetError (FT (GetIncSuspendChunk r) m))
(GetIncEnv s r)
-> GetIncM s r m (GetIncEnv s r)
forall s r (m :: * -> *) a.
ReaderT
(GetIncEnv s r) (ExceptT GetError (FT (GetIncSuspendChunk r) m)) a
-> GetIncM s r m a
GetIncM ReaderT
(GetIncEnv s r)
(ExceptT GetError (FT (GetIncSuspendChunk r) m))
(GetIncEnv s r)
forall r (m :: * -> *). MonadReader r m => m r
ask
ByteCount
gloAbs <- m ByteCount -> GetIncM s r m ByteCount
forall (m :: * -> *) a. Monad m => m a -> GetIncM s r m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (MutVar (PrimState m) ByteCount -> m ByteCount
forall (m :: * -> *) a.
PrimMonad m =>
MutVar (PrimState m) a -> m a
readMutVar MutVar s ByteCount
MutVar (PrimState m) ByteCount
gloAbsRef)
Seq ByteCount
capStack <- m (Seq ByteCount) -> GetIncM s r m (Seq ByteCount)
forall (m :: * -> *) a. Monad m => m a -> GetIncM s r m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (MutVar (PrimState m) (Seq ByteCount) -> m (Seq ByteCount)
forall (m :: * -> *) a.
PrimMonad m =>
MutVar (PrimState m) a -> m a
readMutVar MutVar s (Seq ByteCount)
MutVar (PrimState m) (Seq ByteCount)
capStackRef)
case Seq ByteCount
capStack of
Seq ByteCount
Empty -> GetError -> GetIncM s r m a
forall a. GetError -> GetIncM s r m a
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError (ByteCount -> GetError
GetErrorRemaining ByteCount
gloAbs)
Seq ByteCount
_ :|> ByteCount
cap -> ByteCount -> GetIncM s r m a
k (ByteCount
cap ByteCount -> ByteCount -> ByteCount
forall a. Num a => a -> a -> a
- ByteCount
gloAbs)
GetFFail Text
msg -> GetError -> GetIncM s r m a
forall a. GetError -> GetIncM s r m a
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError (Text -> GetError
GetErrorFail Text
msg)
runGetIncInternal
:: (MonadPrim s m, ReadMem r m)
=> Get a
-> GetIncEnv s r
-> GetIncCbChunk r m
-> m (Either GetError a, ByteCount, ByteCount)
runGetIncInternal :: forall s (m :: * -> *) r a.
(MonadPrim s m, ReadMem r m) =>
Get a
-> GetIncEnv s r
-> GetIncCbChunk r m
-> m (Either GetError a, ByteCount, ByteCount)
runGetIncInternal Get a
getter GetIncEnv s r
env GetIncCbChunk r m
cb = do
let m :: GetIncM s r m a
m = Get a -> GetIncM s r m a
forall s (m :: * -> *) r a.
(MonadPrim s m, ReadMem r m) =>
Get a -> GetIncM s r m a
interpGetInc Get a
getter
Either GetError a
res <- GetIncM s r m a
-> GetIncEnv s r -> GetIncCbChunk r m -> m (Either GetError a)
forall s (m :: * -> *) r a.
MonadPrim s m =>
GetIncM s r m a
-> GetIncEnv s r -> GetIncCbChunk r m -> m (Either GetError a)
runGetIncM GetIncM s r m a
m GetIncEnv s r
env GetIncCbChunk r m
cb
ByteCount
gloAbs <- MutVar (PrimState m) ByteCount -> m ByteCount
forall (m :: * -> *) a.
PrimMonad m =>
MutVar (PrimState m) a -> m a
readMutVar (GetIncEnv s r -> MutVar s ByteCount
forall s r. GetIncEnv s r -> MutVar s ByteCount
gieGlobalAbs GetIncEnv s r
env)
ByteCount
gloRel <- MutVar (PrimState m) ByteCount -> m ByteCount
forall (m :: * -> *) a.
PrimMonad m =>
MutVar (PrimState m) a -> m a
readMutVar (GetIncEnv s r -> MutVar s ByteCount
forall s r. GetIncEnv s r -> MutVar s ByteCount
gieGlobalRel GetIncEnv s r
env)
GetIncChunk r
curChunk <- MutVar (PrimState m) (GetIncChunk r) -> m (GetIncChunk r)
forall (m :: * -> *) a.
PrimMonad m =>
MutVar (PrimState m) a -> m a
readMutVar (GetIncEnv s r -> MutVar s (GetIncChunk r)
forall s r. GetIncEnv s r -> MutVar s (GetIncChunk r)
gieCurChunk GetIncEnv s r
env)
let baseOff :: ByteCount
baseOff = ByteCount
gloAbs ByteCount -> ByteCount -> ByteCount
forall a. Num a => a -> a -> a
- ByteCount
gloRel ByteCount -> ByteCount -> ByteCount
forall a. Num a => a -> a -> a
+ GetIncChunk r -> ByteCount
forall r. GetIncChunk r -> ByteCount
gicLocalOff GetIncChunk r
curChunk
(Either GetError a, ByteCount, ByteCount)
-> m (Either GetError a, ByteCount, ByteCount)
forall a. a -> m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Either GetError a
res, ByteCount
gloAbs, ByteCount
baseOff)
data PutEnv s q = PutEnv
{ forall s (q :: * -> *). PutEnv s q -> MutVar s ByteCount
peOff :: !(MutVar s ByteCount)
, forall s (q :: * -> *). PutEnv s q -> ByteCount
peCap :: !ByteCount
, forall s (q :: * -> *). PutEnv s q -> q s
peArray :: !(q s)
}
newPutEnv :: (PrimMonad m) => ByteCount -> ByteCount -> q (PrimState m) -> m (PutEnv (PrimState m) q)
newPutEnv :: forall (m :: * -> *) (q :: * -> *).
PrimMonad m =>
ByteCount
-> ByteCount -> q (PrimState m) -> m (PutEnv (PrimState m) q)
newPutEnv ByteCount
off ByteCount
cap q (PrimState m)
mem = do
MutVar (PrimState m) ByteCount
offRef <- ByteCount -> m (MutVar (PrimState m) ByteCount)
forall (m :: * -> *) a.
PrimMonad m =>
a -> m (MutVar (PrimState m) a)
newMutVar ByteCount
off
PutEnv (PrimState m) q -> m (PutEnv (PrimState m) q)
forall a. a -> m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (MutVar (PrimState m) ByteCount
-> ByteCount -> q (PrimState m) -> PutEnv (PrimState m) q
forall s (q :: * -> *).
MutVar s ByteCount -> ByteCount -> q s -> PutEnv s q
PutEnv MutVar (PrimState m) ByteCount
offRef ByteCount
cap q (PrimState m)
mem)
newtype PutEff q m a = PutEff {forall (q :: * -> *) (m :: * -> *) a.
PutEff q m a -> ReaderT (PutEnv (PrimState m) q) m a
unPutEff :: ReaderT (PutEnv (PrimState m) q) m a}
deriving newtype ((forall a b. (a -> b) -> PutEff q m a -> PutEff q m b)
-> (forall a b. a -> PutEff q m b -> PutEff q m a)
-> Functor (PutEff q m)
forall a b. a -> PutEff q m b -> PutEff q m a
forall a b. (a -> b) -> PutEff q m a -> PutEff q m b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
forall (q :: * -> *) (m :: * -> *) a b.
Functor m =>
a -> PutEff q m b -> PutEff q m a
forall (q :: * -> *) (m :: * -> *) a b.
Functor m =>
(a -> b) -> PutEff q m a -> PutEff q m b
$cfmap :: forall (q :: * -> *) (m :: * -> *) a b.
Functor m =>
(a -> b) -> PutEff q m a -> PutEff q m b
fmap :: forall a b. (a -> b) -> PutEff q m a -> PutEff q m b
$c<$ :: forall (q :: * -> *) (m :: * -> *) a b.
Functor m =>
a -> PutEff q m b -> PutEff q m a
<$ :: forall a b. a -> PutEff q m b -> PutEff q m a
Functor, Functor (PutEff q m)
Functor (PutEff q m) =>
(forall a. a -> PutEff q m a)
-> (forall a b.
PutEff q m (a -> b) -> PutEff q m a -> PutEff q m b)
-> (forall a b c.
(a -> b -> c) -> PutEff q m a -> PutEff q m b -> PutEff q m c)
-> (forall a b. PutEff q m a -> PutEff q m b -> PutEff q m b)
-> (forall a b. PutEff q m a -> PutEff q m b -> PutEff q m a)
-> Applicative (PutEff q m)
forall a. a -> PutEff q m a
forall a b. PutEff q m a -> PutEff q m b -> PutEff q m a
forall a b. PutEff q m a -> PutEff q m b -> PutEff q m b
forall a b. PutEff q m (a -> b) -> PutEff q m a -> PutEff q m b
forall a b c.
(a -> b -> c) -> PutEff q m a -> PutEff q m b -> PutEff q m c
forall (f :: * -> *).
Functor f =>
(forall a. a -> f a)
-> (forall a b. f (a -> b) -> f a -> f b)
-> (forall a b c. (a -> b -> c) -> f a -> f b -> f c)
-> (forall a b. f a -> f b -> f b)
-> (forall a b. f a -> f b -> f a)
-> Applicative f
forall (q :: * -> *) (m :: * -> *).
Applicative m =>
Functor (PutEff q m)
forall (q :: * -> *) (m :: * -> *) a.
Applicative m =>
a -> PutEff q m a
forall (q :: * -> *) (m :: * -> *) a b.
Applicative m =>
PutEff q m a -> PutEff q m b -> PutEff q m a
forall (q :: * -> *) (m :: * -> *) a b.
Applicative m =>
PutEff q m a -> PutEff q m b -> PutEff q m b
forall (q :: * -> *) (m :: * -> *) a b.
Applicative m =>
PutEff q m (a -> b) -> PutEff q m a -> PutEff q m b
forall (q :: * -> *) (m :: * -> *) a b c.
Applicative m =>
(a -> b -> c) -> PutEff q m a -> PutEff q m b -> PutEff q m c
$cpure :: forall (q :: * -> *) (m :: * -> *) a.
Applicative m =>
a -> PutEff q m a
pure :: forall a. a -> PutEff q m a
$c<*> :: forall (q :: * -> *) (m :: * -> *) a b.
Applicative m =>
PutEff q m (a -> b) -> PutEff q m a -> PutEff q m b
<*> :: forall a b. PutEff q m (a -> b) -> PutEff q m a -> PutEff q m b
$cliftA2 :: forall (q :: * -> *) (m :: * -> *) a b c.
Applicative m =>
(a -> b -> c) -> PutEff q m a -> PutEff q m b -> PutEff q m c
liftA2 :: forall a b c.
(a -> b -> c) -> PutEff q m a -> PutEff q m b -> PutEff q m c
$c*> :: forall (q :: * -> *) (m :: * -> *) a b.
Applicative m =>
PutEff q m a -> PutEff q m b -> PutEff q m b
*> :: forall a b. PutEff q m a -> PutEff q m b -> PutEff q m b
$c<* :: forall (q :: * -> *) (m :: * -> *) a b.
Applicative m =>
PutEff q m a -> PutEff q m b -> PutEff q m a
<* :: forall a b. PutEff q m a -> PutEff q m b -> PutEff q m a
Applicative, Applicative (PutEff q m)
Applicative (PutEff q m) =>
(forall a b. PutEff q m a -> (a -> PutEff q m b) -> PutEff q m b)
-> (forall a b. PutEff q m a -> PutEff q m b -> PutEff q m b)
-> (forall a. a -> PutEff q m a)
-> Monad (PutEff q m)
forall a. a -> PutEff q m a
forall a b. PutEff q m a -> PutEff q m b -> PutEff q m b
forall a b. PutEff q m a -> (a -> PutEff q m b) -> PutEff q m b
forall (m :: * -> *).
Applicative m =>
(forall a b. m a -> (a -> m b) -> m b)
-> (forall a b. m a -> m b -> m b)
-> (forall a. a -> m a)
-> Monad m
forall (q :: * -> *) (m :: * -> *).
Monad m =>
Applicative (PutEff q m)
forall (q :: * -> *) (m :: * -> *) a. Monad m => a -> PutEff q m a
forall (q :: * -> *) (m :: * -> *) a b.
Monad m =>
PutEff q m a -> PutEff q m b -> PutEff q m b
forall (q :: * -> *) (m :: * -> *) a b.
Monad m =>
PutEff q m a -> (a -> PutEff q m b) -> PutEff q m b
$c>>= :: forall (q :: * -> *) (m :: * -> *) a b.
Monad m =>
PutEff q m a -> (a -> PutEff q m b) -> PutEff q m b
>>= :: forall a b. PutEff q m a -> (a -> PutEff q m b) -> PutEff q m b
$c>> :: forall (q :: * -> *) (m :: * -> *) a b.
Monad m =>
PutEff q m a -> PutEff q m b -> PutEff q m b
>> :: forall a b. PutEff q m a -> PutEff q m b -> PutEff q m b
$creturn :: forall (q :: * -> *) (m :: * -> *) a. Monad m => a -> PutEff q m a
return :: forall a. a -> PutEff q m a
Monad)
deriving newtype instance (Monad m, s ~ PrimState m) => MonadReader (PutEnv s q) (PutEff q m)
runPutEff :: PutEff q m a -> PutEnv (PrimState m) q -> m a
runPutEff :: forall (q :: * -> *) (m :: * -> *) a.
PutEff q m a -> PutEnv (PrimState m) q -> m a
runPutEff PutEff q m a
act = ReaderT (PutEnv (PrimState m) q) m a
-> PutEnv (PrimState m) q -> m a
forall r (m :: * -> *) a. ReaderT r m a -> r -> m a
runReaderT (PutEff q m a -> ReaderT (PutEnv (PrimState m) q) m a
forall (q :: * -> *) (m :: * -> *) a.
PutEff q m a -> ReaderT (PutEnv (PrimState m) q) m a
unPutEff PutEff q m a
act)
stPutEff :: (Monad m) => m a -> PutEff q m a
stPutEff :: forall (m :: * -> *) a (q :: * -> *).
Monad m =>
m a -> PutEff q m a
stPutEff = ReaderT (PutEnv (PrimState m) q) m a -> PutEff q m a
forall (q :: * -> *) (m :: * -> *) a.
ReaderT (PutEnv (PrimState m) q) m a -> PutEff q m a
PutEff (ReaderT (PutEnv (PrimState m) q) m a -> PutEff q m a)
-> (m a -> ReaderT (PutEnv (PrimState m) q) m a)
-> m a
-> PutEff q m a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. m a -> ReaderT (PutEnv (PrimState m) q) m a
forall (m :: * -> *) a.
Monad m =>
m a -> ReaderT (PutEnv (PrimState m) q) m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift
newtype PutRun q m a = PutRun {forall (q :: * -> *) (m :: * -> *) a.
PutRun q m a -> FT PutF (PutEff q m) a
unPutRun :: FT PutF (PutEff q m) a}
deriving newtype ((forall a b. (a -> b) -> PutRun q m a -> PutRun q m b)
-> (forall a b. a -> PutRun q m b -> PutRun q m a)
-> Functor (PutRun q m)
forall a b. a -> PutRun q m b -> PutRun q m a
forall a b. (a -> b) -> PutRun q m a -> PutRun q m b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
forall (q :: * -> *) (m :: * -> *) a b.
a -> PutRun q m b -> PutRun q m a
forall (q :: * -> *) (m :: * -> *) a b.
(a -> b) -> PutRun q m a -> PutRun q m b
$cfmap :: forall (q :: * -> *) (m :: * -> *) a b.
(a -> b) -> PutRun q m a -> PutRun q m b
fmap :: forall a b. (a -> b) -> PutRun q m a -> PutRun q m b
$c<$ :: forall (q :: * -> *) (m :: * -> *) a b.
a -> PutRun q m b -> PutRun q m a
<$ :: forall a b. a -> PutRun q m b -> PutRun q m a
Functor, Functor (PutRun q m)
Functor (PutRun q m) =>
(forall a. a -> PutRun q m a)
-> (forall a b.
PutRun q m (a -> b) -> PutRun q m a -> PutRun q m b)
-> (forall a b c.
(a -> b -> c) -> PutRun q m a -> PutRun q m b -> PutRun q m c)
-> (forall a b. PutRun q m a -> PutRun q m b -> PutRun q m b)
-> (forall a b. PutRun q m a -> PutRun q m b -> PutRun q m a)
-> Applicative (PutRun q m)
forall a. a -> PutRun q m a
forall a b. PutRun q m a -> PutRun q m b -> PutRun q m a
forall a b. PutRun q m a -> PutRun q m b -> PutRun q m b
forall a b. PutRun q m (a -> b) -> PutRun q m a -> PutRun q m b
forall a b c.
(a -> b -> c) -> PutRun q m a -> PutRun q m b -> PutRun q m c
forall (f :: * -> *).
Functor f =>
(forall a. a -> f a)
-> (forall a b. f (a -> b) -> f a -> f b)
-> (forall a b c. (a -> b -> c) -> f a -> f b -> f c)
-> (forall a b. f a -> f b -> f b)
-> (forall a b. f a -> f b -> f a)
-> Applicative f
forall (q :: * -> *) (m :: * -> *). Functor (PutRun q m)
forall (q :: * -> *) (m :: * -> *) a. a -> PutRun q m a
forall (q :: * -> *) (m :: * -> *) a b.
PutRun q m a -> PutRun q m b -> PutRun q m a
forall (q :: * -> *) (m :: * -> *) a b.
PutRun q m a -> PutRun q m b -> PutRun q m b
forall (q :: * -> *) (m :: * -> *) a b.
PutRun q m (a -> b) -> PutRun q m a -> PutRun q m b
forall (q :: * -> *) (m :: * -> *) a b c.
(a -> b -> c) -> PutRun q m a -> PutRun q m b -> PutRun q m c
$cpure :: forall (q :: * -> *) (m :: * -> *) a. a -> PutRun q m a
pure :: forall a. a -> PutRun q m a
$c<*> :: forall (q :: * -> *) (m :: * -> *) a b.
PutRun q m (a -> b) -> PutRun q m a -> PutRun q m b
<*> :: forall a b. PutRun q m (a -> b) -> PutRun q m a -> PutRun q m b
$cliftA2 :: forall (q :: * -> *) (m :: * -> *) a b c.
(a -> b -> c) -> PutRun q m a -> PutRun q m b -> PutRun q m c
liftA2 :: forall a b c.
(a -> b -> c) -> PutRun q m a -> PutRun q m b -> PutRun q m c
$c*> :: forall (q :: * -> *) (m :: * -> *) a b.
PutRun q m a -> PutRun q m b -> PutRun q m b
*> :: forall a b. PutRun q m a -> PutRun q m b -> PutRun q m b
$c<* :: forall (q :: * -> *) (m :: * -> *) a b.
PutRun q m a -> PutRun q m b -> PutRun q m a
<* :: forall a b. PutRun q m a -> PutRun q m b -> PutRun q m a
Applicative, Applicative (PutRun q m)
Applicative (PutRun q m) =>
(forall a b. PutRun q m a -> (a -> PutRun q m b) -> PutRun q m b)
-> (forall a b. PutRun q m a -> PutRun q m b -> PutRun q m b)
-> (forall a. a -> PutRun q m a)
-> Monad (PutRun q m)
forall a. a -> PutRun q m a
forall a b. PutRun q m a -> PutRun q m b -> PutRun q m b
forall a b. PutRun q m a -> (a -> PutRun q m b) -> PutRun q m b
forall (m :: * -> *).
Applicative m =>
(forall a b. m a -> (a -> m b) -> m b)
-> (forall a b. m a -> m b -> m b)
-> (forall a. a -> m a)
-> Monad m
forall (q :: * -> *) (m :: * -> *). Applicative (PutRun q m)
forall (q :: * -> *) (m :: * -> *) a. a -> PutRun q m a
forall (q :: * -> *) (m :: * -> *) a b.
PutRun q m a -> PutRun q m b -> PutRun q m b
forall (q :: * -> *) (m :: * -> *) a b.
PutRun q m a -> (a -> PutRun q m b) -> PutRun q m b
$c>>= :: forall (q :: * -> *) (m :: * -> *) a b.
PutRun q m a -> (a -> PutRun q m b) -> PutRun q m b
>>= :: forall a b. PutRun q m a -> (a -> PutRun q m b) -> PutRun q m b
$c>> :: forall (q :: * -> *) (m :: * -> *) a b.
PutRun q m a -> PutRun q m b -> PutRun q m b
>> :: forall a b. PutRun q m a -> PutRun q m b -> PutRun q m b
$creturn :: forall (q :: * -> *) (m :: * -> *) a. a -> PutRun q m a
return :: forall a. a -> PutRun q m a
Monad)
writeBytes :: (PrimMonad m) => ByteCount -> (q (PrimState m) -> ByteCount -> m ()) -> PutEff q m ()
writeBytes :: forall (m :: * -> *) (q :: * -> *).
PrimMonad m =>
ByteCount
-> (q (PrimState m) -> ByteCount -> m ()) -> PutEff q m ()
writeBytes ByteCount
bc q (PrimState m) -> ByteCount -> m ()
f = do
PutEnv MutVar (PrimState m) ByteCount
offRef ByteCount
_ q (PrimState m)
mem <- PutEff q m (PutEnv (PrimState m) q)
forall r (m :: * -> *). MonadReader r m => m r
ask
m () -> PutEff q m ()
forall (m :: * -> *) a (q :: * -> *).
Monad m =>
m a -> PutEff q m a
stPutEff (m () -> PutEff q m ()) -> m () -> PutEff q m ()
forall a b. (a -> b) -> a -> b
$ do
ByteCount
off <- MutVar (PrimState m) ByteCount -> m ByteCount
forall (m :: * -> *) a.
PrimMonad m =>
MutVar (PrimState m) a -> m a
readMutVar MutVar (PrimState m) ByteCount
offRef
q (PrimState m) -> ByteCount -> m ()
f q (PrimState m)
mem ByteCount
off
let newOff :: ByteCount
newOff = ByteCount
off ByteCount -> ByteCount -> ByteCount
forall a. Num a => a -> a -> a
+ ByteCount
bc
MutVar (PrimState m) ByteCount -> ByteCount -> m ()
forall (m :: * -> *) a.
PrimMonad m =>
MutVar (PrimState m) a -> a -> m ()
writeMutVar MutVar (PrimState m) ByteCount
offRef ByteCount
newOff
writeStaticSeq :: (WriteMem q m) => PutStaticSeqF (PutEff q m a) -> PutEff q m a
writeStaticSeq :: forall (q :: * -> *) (m :: * -> *) a.
WriteMem q m =>
PutStaticSeqF (PutEff q m a) -> PutEff q m a
writeStaticSeq (PutStaticSeqF ElemCount
n Maybe z
mz z -> Put
p Seq z
s PutEff q m a
k) = do
[z] -> (z -> PutEff q m ()) -> PutEff q m ()
forall (t :: * -> *) (f :: * -> *) a b.
(Foldable t, Applicative f) =>
t a -> (a -> f b) -> f ()
for_ (Int -> [z] -> [z]
forall a. Int -> [a] -> [a]
take (ElemCount -> Int
forall a b. Coercible a b => a -> b
coerce ElemCount
n) (Seq z -> [z]
forall a. Seq a -> [a]
forall (t :: * -> *) a. Foldable t => t a -> [a]
toList Seq z
s)) ((z -> PutEff q m ()) -> PutEff q m ())
-> (z -> PutEff q m ()) -> PutEff q m ()
forall a b. (a -> b) -> a -> b
$ \z
a -> do
Put -> PutEff q m ()
forall (q :: * -> *) (m :: * -> *) a.
WriteMem q m =>
PutM a -> PutEff q m a
mkPutEff (z -> Put
p z
a)
let e :: Int
e = Seq z -> Int
forall a. Seq a -> Int
Seq.length Seq z
s
Bool -> PutEff q m () -> PutEff q m ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (ElemCount -> Int
forall a b. Coercible a b => a -> b
coerce ElemCount
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
e) (PutEff q m () -> PutEff q m ()) -> PutEff q m () -> PutEff q m ()
forall a b. (a -> b) -> a -> b
$ do
let q :: PutEff q m ()
q = Put -> PutEff q m ()
forall (q :: * -> *) (m :: * -> *) a.
WriteMem q m =>
PutM a -> PutEff q m a
mkPutEff (z -> Put
p (Maybe z -> z
forall a. HasCallStack => Maybe a -> a
fromJust Maybe z
mz))
Int -> PutEff q m () -> PutEff q m ()
forall (m :: * -> *) a. Applicative m => Int -> m a -> m ()
replicateM_ (ElemCount -> Int
forall a b. Coercible a b => a -> b
coerce ElemCount
n Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
e) PutEff q m ()
q
PutEff q m a
k
writeStaticArray :: (WriteMem q m) => PutStaticArrayF (PutEff q m a) -> PutEff q m a
writeStaticArray :: forall (q :: * -> *) (m :: * -> *) a.
WriteMem q m =>
PutStaticArrayF (PutEff q m a) -> PutEff q m a
writeStaticArray psa :: PutStaticArrayF (PutEff q m a)
psa@(PutStaticArrayF ElemCount
needElems Maybe z
mz pa :: PrimArray z
pa@(PrimArray ByteArray#
ba) PutEff q m a
k) = do
let elemSize :: ByteCount
elemSize = PutStaticArrayF (PutEff q m a) -> ByteCount
forall a. PutStaticArrayF a -> ByteCount
putStaticArrayElemSize PutStaticArrayF (PutEff q m a)
psa
haveElems :: ElemCount
haveElems = Int -> ElemCount
ElemCount (PrimArray z -> Int
forall a. Prim a => PrimArray a -> Int
sizeofPrimArray PrimArray z
pa)
useElems :: ElemCount
useElems = ElemCount -> ElemCount -> ElemCount
forall a. Ord a => a -> a -> a
min ElemCount
haveElems ElemCount
needElems
useBc :: ByteCount
useBc = ByteCount
elemSize ByteCount -> ByteCount -> ByteCount
forall a. Num a => a -> a -> a
* ElemCount -> ByteCount
forall a b. Coercible a b => a -> b
coerce ElemCount
useElems
ByteCount
-> (q (PrimState m) -> ByteCount -> m ()) -> PutEff q m ()
forall (m :: * -> *) (q :: * -> *).
PrimMonad m =>
ByteCount
-> (q (PrimState m) -> ByteCount -> m ()) -> PutEff q m ()
writeBytes ByteCount
useBc (ByteArray
-> ByteCount -> ByteCount -> q (PrimState m) -> ByteCount -> m ()
forall (q :: * -> *) (m :: * -> *).
WriteMem q m =>
ByteArray
-> ByteCount -> ByteCount -> q (PrimState m) -> ByteCount -> m ()
copyArrayMemInBytes (ByteArray# -> ByteArray
ByteArray ByteArray#
ba) ByteCount
0 ByteCount
useBc)
let needBc :: ByteCount
needBc = PutStaticArrayF (PutEff q m a) -> ByteCount
forall a. PutStaticArrayF a -> ByteCount
putStaticArraySize PutStaticArrayF (PutEff q m a)
psa
Bool -> PutEff q m () -> PutEff q m ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (ByteCount
useBc ByteCount -> ByteCount -> Bool
forall a. Eq a => a -> a -> Bool
== ByteCount
needBc) (PutEff q m () -> PutEff q m ()) -> PutEff q m () -> PutEff q m ()
forall a b. (a -> b) -> a -> b
$ do
let extraBc :: ByteCount
extraBc = ByteCount
needBc ByteCount -> ByteCount -> ByteCount
forall a. Num a => a -> a -> a
- ByteCount
useBc
case Maybe z
mz of
Maybe z
Nothing -> String -> PutEff q m ()
forall a. HasCallStack => String -> a
error String
"no default element for undersized static array"
Just z
z -> ByteCount
-> (q (PrimState m) -> ByteCount -> m ()) -> PutEff q m ()
forall (m :: * -> *) (q :: * -> *).
PrimMonad m =>
ByteCount
-> (q (PrimState m) -> ByteCount -> m ()) -> PutEff q m ()
writeBytes ByteCount
extraBc (ByteCount -> z -> q (PrimState m) -> ByteCount -> m ()
forall a.
(Prim a, PrimUnaligned a) =>
ByteCount -> a -> q (PrimState m) -> ByteCount -> m ()
forall (q :: * -> *) (m :: * -> *) a.
(WriteMem q m, Prim a, PrimUnaligned a) =>
ByteCount -> a -> q (PrimState m) -> ByteCount -> m ()
setMemInBytes ByteCount
extraBc z
z)
PutEff q m a
k
execPutRun :: (WriteMem q m) => PutF (PutEff q m a) -> PutEff q m a
execPutRun :: forall (q :: * -> *) (m :: * -> *) a.
WriteMem q m =>
PutF (PutEff q m a) -> PutEff q m a
execPutRun = \case
PutFWord8 Word8
x PutEff q m a
k -> ByteCount
-> (q (PrimState m) -> ByteCount -> m ()) -> PutEff q m ()
forall (m :: * -> *) (q :: * -> *).
PrimMonad m =>
ByteCount
-> (q (PrimState m) -> ByteCount -> m ()) -> PutEff q m ()
writeBytes ByteCount
1 (Word8 -> q (PrimState m) -> ByteCount -> m ()
forall a.
(Prim a, PrimUnaligned a) =>
a -> q (PrimState m) -> ByteCount -> m ()
forall (q :: * -> *) (m :: * -> *) a.
(WriteMem q m, Prim a, PrimUnaligned a) =>
a -> q (PrimState m) -> ByteCount -> m ()
writeMemInBytes Word8
x) PutEff q m () -> PutEff q m a -> PutEff q m a
forall a b. PutEff q m a -> PutEff q m b -> PutEff q m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> PutEff q m a
k
PutFInt8 Int8
x PutEff q m a
k -> ByteCount
-> (q (PrimState m) -> ByteCount -> m ()) -> PutEff q m ()
forall (m :: * -> *) (q :: * -> *).
PrimMonad m =>
ByteCount
-> (q (PrimState m) -> ByteCount -> m ()) -> PutEff q m ()
writeBytes ByteCount
1 (Int8 -> q (PrimState m) -> ByteCount -> m ()
forall a.
(Prim a, PrimUnaligned a) =>
a -> q (PrimState m) -> ByteCount -> m ()
forall (q :: * -> *) (m :: * -> *) a.
(WriteMem q m, Prim a, PrimUnaligned a) =>
a -> q (PrimState m) -> ByteCount -> m ()
writeMemInBytes Int8
x) PutEff q m () -> PutEff q m a -> PutEff q m a
forall a b. PutEff q m a -> PutEff q m b -> PutEff q m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> PutEff q m a
k
PutFWord16LE Word16LE
x PutEff q m a
k -> ByteCount
-> (q (PrimState m) -> ByteCount -> m ()) -> PutEff q m ()
forall (m :: * -> *) (q :: * -> *).
PrimMonad m =>
ByteCount
-> (q (PrimState m) -> ByteCount -> m ()) -> PutEff q m ()
writeBytes ByteCount
2 (Word16LE -> q (PrimState m) -> ByteCount -> m ()
forall a.
(Prim a, PrimUnaligned a) =>
a -> q (PrimState m) -> ByteCount -> m ()
forall (q :: * -> *) (m :: * -> *) a.
(WriteMem q m, Prim a, PrimUnaligned a) =>
a -> q (PrimState m) -> ByteCount -> m ()
writeMemInBytes Word16LE
x) PutEff q m () -> PutEff q m a -> PutEff q m a
forall a b. PutEff q m a -> PutEff q m b -> PutEff q m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> PutEff q m a
k
PutFInt16LE Int16LE
x PutEff q m a
k -> ByteCount
-> (q (PrimState m) -> ByteCount -> m ()) -> PutEff q m ()
forall (m :: * -> *) (q :: * -> *).
PrimMonad m =>
ByteCount
-> (q (PrimState m) -> ByteCount -> m ()) -> PutEff q m ()
writeBytes ByteCount
2 (Int16LE -> q (PrimState m) -> ByteCount -> m ()
forall a.
(Prim a, PrimUnaligned a) =>
a -> q (PrimState m) -> ByteCount -> m ()
forall (q :: * -> *) (m :: * -> *) a.
(WriteMem q m, Prim a, PrimUnaligned a) =>
a -> q (PrimState m) -> ByteCount -> m ()
writeMemInBytes Int16LE
x) PutEff q m () -> PutEff q m a -> PutEff q m a
forall a b. PutEff q m a -> PutEff q m b -> PutEff q m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> PutEff q m a
k
PutFWord24LE Word24LE
x PutEff q m a
k -> ByteCount
-> (q (PrimState m) -> ByteCount -> m ()) -> PutEff q m ()
forall (m :: * -> *) (q :: * -> *).
PrimMonad m =>
ByteCount
-> (q (PrimState m) -> ByteCount -> m ()) -> PutEff q m ()
writeBytes ByteCount
3 (Word24LE -> q (PrimState m) -> ByteCount -> m ()
forall a.
(Prim a, PrimUnaligned a) =>
a -> q (PrimState m) -> ByteCount -> m ()
forall (q :: * -> *) (m :: * -> *) a.
(WriteMem q m, Prim a, PrimUnaligned a) =>
a -> q (PrimState m) -> ByteCount -> m ()
writeMemInBytes Word24LE
x) PutEff q m () -> PutEff q m a -> PutEff q m a
forall a b. PutEff q m a -> PutEff q m b -> PutEff q m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> PutEff q m a
k
PutFInt24LE Int24LE
x PutEff q m a
k -> ByteCount
-> (q (PrimState m) -> ByteCount -> m ()) -> PutEff q m ()
forall (m :: * -> *) (q :: * -> *).
PrimMonad m =>
ByteCount
-> (q (PrimState m) -> ByteCount -> m ()) -> PutEff q m ()
writeBytes ByteCount
3 (Int24LE -> q (PrimState m) -> ByteCount -> m ()
forall a.
(Prim a, PrimUnaligned a) =>
a -> q (PrimState m) -> ByteCount -> m ()
forall (q :: * -> *) (m :: * -> *) a.
(WriteMem q m, Prim a, PrimUnaligned a) =>
a -> q (PrimState m) -> ByteCount -> m ()
writeMemInBytes Int24LE
x) PutEff q m () -> PutEff q m a -> PutEff q m a
forall a b. PutEff q m a -> PutEff q m b -> PutEff q m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> PutEff q m a
k
PutFWord32LE Word32LE
x PutEff q m a
k -> ByteCount
-> (q (PrimState m) -> ByteCount -> m ()) -> PutEff q m ()
forall (m :: * -> *) (q :: * -> *).
PrimMonad m =>
ByteCount
-> (q (PrimState m) -> ByteCount -> m ()) -> PutEff q m ()
writeBytes ByteCount
4 (Word32LE -> q (PrimState m) -> ByteCount -> m ()
forall a.
(Prim a, PrimUnaligned a) =>
a -> q (PrimState m) -> ByteCount -> m ()
forall (q :: * -> *) (m :: * -> *) a.
(WriteMem q m, Prim a, PrimUnaligned a) =>
a -> q (PrimState m) -> ByteCount -> m ()
writeMemInBytes Word32LE
x) PutEff q m () -> PutEff q m a -> PutEff q m a
forall a b. PutEff q m a -> PutEff q m b -> PutEff q m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> PutEff q m a
k
PutFInt32LE Int32LE
x PutEff q m a
k -> ByteCount
-> (q (PrimState m) -> ByteCount -> m ()) -> PutEff q m ()
forall (m :: * -> *) (q :: * -> *).
PrimMonad m =>
ByteCount
-> (q (PrimState m) -> ByteCount -> m ()) -> PutEff q m ()
writeBytes ByteCount
4 (Int32LE -> q (PrimState m) -> ByteCount -> m ()
forall a.
(Prim a, PrimUnaligned a) =>
a -> q (PrimState m) -> ByteCount -> m ()
forall (q :: * -> *) (m :: * -> *) a.
(WriteMem q m, Prim a, PrimUnaligned a) =>
a -> q (PrimState m) -> ByteCount -> m ()
writeMemInBytes Int32LE
x) PutEff q m () -> PutEff q m a -> PutEff q m a
forall a b. PutEff q m a -> PutEff q m b -> PutEff q m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> PutEff q m a
k
PutFWord64LE Word64LE
x PutEff q m a
k -> ByteCount
-> (q (PrimState m) -> ByteCount -> m ()) -> PutEff q m ()
forall (m :: * -> *) (q :: * -> *).
PrimMonad m =>
ByteCount
-> (q (PrimState m) -> ByteCount -> m ()) -> PutEff q m ()
writeBytes ByteCount
8 (Word64LE -> q (PrimState m) -> ByteCount -> m ()
forall a.
(Prim a, PrimUnaligned a) =>
a -> q (PrimState m) -> ByteCount -> m ()
forall (q :: * -> *) (m :: * -> *) a.
(WriteMem q m, Prim a, PrimUnaligned a) =>
a -> q (PrimState m) -> ByteCount -> m ()
writeMemInBytes Word64LE
x) PutEff q m () -> PutEff q m a -> PutEff q m a
forall a b. PutEff q m a -> PutEff q m b -> PutEff q m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> PutEff q m a
k
PutFInt64LE Int64LE
x PutEff q m a
k -> ByteCount
-> (q (PrimState m) -> ByteCount -> m ()) -> PutEff q m ()
forall (m :: * -> *) (q :: * -> *).
PrimMonad m =>
ByteCount
-> (q (PrimState m) -> ByteCount -> m ()) -> PutEff q m ()
writeBytes ByteCount
8 (Int64LE -> q (PrimState m) -> ByteCount -> m ()
forall a.
(Prim a, PrimUnaligned a) =>
a -> q (PrimState m) -> ByteCount -> m ()
forall (q :: * -> *) (m :: * -> *) a.
(WriteMem q m, Prim a, PrimUnaligned a) =>
a -> q (PrimState m) -> ByteCount -> m ()
writeMemInBytes Int64LE
x) PutEff q m () -> PutEff q m a -> PutEff q m a
forall a b. PutEff q m a -> PutEff q m b -> PutEff q m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> PutEff q m a
k
PutFFloatLE FloatLE
x PutEff q m a
k -> ByteCount
-> (q (PrimState m) -> ByteCount -> m ()) -> PutEff q m ()
forall (m :: * -> *) (q :: * -> *).
PrimMonad m =>
ByteCount
-> (q (PrimState m) -> ByteCount -> m ()) -> PutEff q m ()
writeBytes ByteCount
4 (FloatLE -> q (PrimState m) -> ByteCount -> m ()
forall a.
(Prim a, PrimUnaligned a) =>
a -> q (PrimState m) -> ByteCount -> m ()
forall (q :: * -> *) (m :: * -> *) a.
(WriteMem q m, Prim a, PrimUnaligned a) =>
a -> q (PrimState m) -> ByteCount -> m ()
writeMemInBytes FloatLE
x) PutEff q m () -> PutEff q m a -> PutEff q m a
forall a b. PutEff q m a -> PutEff q m b -> PutEff q m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> PutEff q m a
k
PutFDoubleLE DoubleLE
x PutEff q m a
k -> ByteCount
-> (q (PrimState m) -> ByteCount -> m ()) -> PutEff q m ()
forall (m :: * -> *) (q :: * -> *).
PrimMonad m =>
ByteCount
-> (q (PrimState m) -> ByteCount -> m ()) -> PutEff q m ()
writeBytes ByteCount
8 (DoubleLE -> q (PrimState m) -> ByteCount -> m ()
forall a.
(Prim a, PrimUnaligned a) =>
a -> q (PrimState m) -> ByteCount -> m ()
forall (q :: * -> *) (m :: * -> *) a.
(WriteMem q m, Prim a, PrimUnaligned a) =>
a -> q (PrimState m) -> ByteCount -> m ()
writeMemInBytes DoubleLE
x) PutEff q m () -> PutEff q m a -> PutEff q m a
forall a b. PutEff q m a -> PutEff q m b -> PutEff q m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> PutEff q m a
k
PutFWord16BE Word16BE
x PutEff q m a
k -> ByteCount
-> (q (PrimState m) -> ByteCount -> m ()) -> PutEff q m ()
forall (m :: * -> *) (q :: * -> *).
PrimMonad m =>
ByteCount
-> (q (PrimState m) -> ByteCount -> m ()) -> PutEff q m ()
writeBytes ByteCount
2 (Word16BE -> q (PrimState m) -> ByteCount -> m ()
forall a.
(Prim a, PrimUnaligned a) =>
a -> q (PrimState m) -> ByteCount -> m ()
forall (q :: * -> *) (m :: * -> *) a.
(WriteMem q m, Prim a, PrimUnaligned a) =>
a -> q (PrimState m) -> ByteCount -> m ()
writeMemInBytes Word16BE
x) PutEff q m () -> PutEff q m a -> PutEff q m a
forall a b. PutEff q m a -> PutEff q m b -> PutEff q m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> PutEff q m a
k
PutFInt16BE Int16BE
x PutEff q m a
k -> ByteCount
-> (q (PrimState m) -> ByteCount -> m ()) -> PutEff q m ()
forall (m :: * -> *) (q :: * -> *).
PrimMonad m =>
ByteCount
-> (q (PrimState m) -> ByteCount -> m ()) -> PutEff q m ()
writeBytes ByteCount
2 (Int16BE -> q (PrimState m) -> ByteCount -> m ()
forall a.
(Prim a, PrimUnaligned a) =>
a -> q (PrimState m) -> ByteCount -> m ()
forall (q :: * -> *) (m :: * -> *) a.
(WriteMem q m, Prim a, PrimUnaligned a) =>
a -> q (PrimState m) -> ByteCount -> m ()
writeMemInBytes Int16BE
x) PutEff q m () -> PutEff q m a -> PutEff q m a
forall a b. PutEff q m a -> PutEff q m b -> PutEff q m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> PutEff q m a
k
PutFWord24BE Word24BE
x PutEff q m a
k -> ByteCount
-> (q (PrimState m) -> ByteCount -> m ()) -> PutEff q m ()
forall (m :: * -> *) (q :: * -> *).
PrimMonad m =>
ByteCount
-> (q (PrimState m) -> ByteCount -> m ()) -> PutEff q m ()
writeBytes ByteCount
3 (Word24BE -> q (PrimState m) -> ByteCount -> m ()
forall a.
(Prim a, PrimUnaligned a) =>
a -> q (PrimState m) -> ByteCount -> m ()
forall (q :: * -> *) (m :: * -> *) a.
(WriteMem q m, Prim a, PrimUnaligned a) =>
a -> q (PrimState m) -> ByteCount -> m ()
writeMemInBytes Word24BE
x) PutEff q m () -> PutEff q m a -> PutEff q m a
forall a b. PutEff q m a -> PutEff q m b -> PutEff q m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> PutEff q m a
k
PutFInt24BE Int24BE
x PutEff q m a
k -> ByteCount
-> (q (PrimState m) -> ByteCount -> m ()) -> PutEff q m ()
forall (m :: * -> *) (q :: * -> *).
PrimMonad m =>
ByteCount
-> (q (PrimState m) -> ByteCount -> m ()) -> PutEff q m ()
writeBytes ByteCount
3 (Int24BE -> q (PrimState m) -> ByteCount -> m ()
forall a.
(Prim a, PrimUnaligned a) =>
a -> q (PrimState m) -> ByteCount -> m ()
forall (q :: * -> *) (m :: * -> *) a.
(WriteMem q m, Prim a, PrimUnaligned a) =>
a -> q (PrimState m) -> ByteCount -> m ()
writeMemInBytes Int24BE
x) PutEff q m () -> PutEff q m a -> PutEff q m a
forall a b. PutEff q m a -> PutEff q m b -> PutEff q m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> PutEff q m a
k
PutFWord32BE Word32BE
x PutEff q m a
k -> ByteCount
-> (q (PrimState m) -> ByteCount -> m ()) -> PutEff q m ()
forall (m :: * -> *) (q :: * -> *).
PrimMonad m =>
ByteCount
-> (q (PrimState m) -> ByteCount -> m ()) -> PutEff q m ()
writeBytes ByteCount
4 (Word32BE -> q (PrimState m) -> ByteCount -> m ()
forall a.
(Prim a, PrimUnaligned a) =>
a -> q (PrimState m) -> ByteCount -> m ()
forall (q :: * -> *) (m :: * -> *) a.
(WriteMem q m, Prim a, PrimUnaligned a) =>
a -> q (PrimState m) -> ByteCount -> m ()
writeMemInBytes Word32BE
x) PutEff q m () -> PutEff q m a -> PutEff q m a
forall a b. PutEff q m a -> PutEff q m b -> PutEff q m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> PutEff q m a
k
PutFInt32BE Int32BE
x PutEff q m a
k -> ByteCount
-> (q (PrimState m) -> ByteCount -> m ()) -> PutEff q m ()
forall (m :: * -> *) (q :: * -> *).
PrimMonad m =>
ByteCount
-> (q (PrimState m) -> ByteCount -> m ()) -> PutEff q m ()
writeBytes ByteCount
4 (Int32BE -> q (PrimState m) -> ByteCount -> m ()
forall a.
(Prim a, PrimUnaligned a) =>
a -> q (PrimState m) -> ByteCount -> m ()
forall (q :: * -> *) (m :: * -> *) a.
(WriteMem q m, Prim a, PrimUnaligned a) =>
a -> q (PrimState m) -> ByteCount -> m ()
writeMemInBytes Int32BE
x) PutEff q m () -> PutEff q m a -> PutEff q m a
forall a b. PutEff q m a -> PutEff q m b -> PutEff q m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> PutEff q m a
k
PutFWord64BE Word64BE
x PutEff q m a
k -> ByteCount
-> (q (PrimState m) -> ByteCount -> m ()) -> PutEff q m ()
forall (m :: * -> *) (q :: * -> *).
PrimMonad m =>
ByteCount
-> (q (PrimState m) -> ByteCount -> m ()) -> PutEff q m ()
writeBytes ByteCount
8 (Word64BE -> q (PrimState m) -> ByteCount -> m ()
forall a.
(Prim a, PrimUnaligned a) =>
a -> q (PrimState m) -> ByteCount -> m ()
forall (q :: * -> *) (m :: * -> *) a.
(WriteMem q m, Prim a, PrimUnaligned a) =>
a -> q (PrimState m) -> ByteCount -> m ()
writeMemInBytes Word64BE
x) PutEff q m () -> PutEff q m a -> PutEff q m a
forall a b. PutEff q m a -> PutEff q m b -> PutEff q m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> PutEff q m a
k
PutFInt64BE Int64BE
x PutEff q m a
k -> ByteCount
-> (q (PrimState m) -> ByteCount -> m ()) -> PutEff q m ()
forall (m :: * -> *) (q :: * -> *).
PrimMonad m =>
ByteCount
-> (q (PrimState m) -> ByteCount -> m ()) -> PutEff q m ()
writeBytes ByteCount
8 (Int64BE -> q (PrimState m) -> ByteCount -> m ()
forall a.
(Prim a, PrimUnaligned a) =>
a -> q (PrimState m) -> ByteCount -> m ()
forall (q :: * -> *) (m :: * -> *) a.
(WriteMem q m, Prim a, PrimUnaligned a) =>
a -> q (PrimState m) -> ByteCount -> m ()
writeMemInBytes Int64BE
x) PutEff q m () -> PutEff q m a -> PutEff q m a
forall a b. PutEff q m a -> PutEff q m b -> PutEff q m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> PutEff q m a
k
PutFFloatBE FloatBE
x PutEff q m a
k -> ByteCount
-> (q (PrimState m) -> ByteCount -> m ()) -> PutEff q m ()
forall (m :: * -> *) (q :: * -> *).
PrimMonad m =>
ByteCount
-> (q (PrimState m) -> ByteCount -> m ()) -> PutEff q m ()
writeBytes ByteCount
4 (FloatBE -> q (PrimState m) -> ByteCount -> m ()
forall a.
(Prim a, PrimUnaligned a) =>
a -> q (PrimState m) -> ByteCount -> m ()
forall (q :: * -> *) (m :: * -> *) a.
(WriteMem q m, Prim a, PrimUnaligned a) =>
a -> q (PrimState m) -> ByteCount -> m ()
writeMemInBytes FloatBE
x) PutEff q m () -> PutEff q m a -> PutEff q m a
forall a b. PutEff q m a -> PutEff q m b -> PutEff q m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> PutEff q m a
k
PutFDoubleBE DoubleBE
x PutEff q m a
k -> ByteCount
-> (q (PrimState m) -> ByteCount -> m ()) -> PutEff q m ()
forall (m :: * -> *) (q :: * -> *).
PrimMonad m =>
ByteCount
-> (q (PrimState m) -> ByteCount -> m ()) -> PutEff q m ()
writeBytes ByteCount
8 (DoubleBE -> q (PrimState m) -> ByteCount -> m ()
forall a.
(Prim a, PrimUnaligned a) =>
a -> q (PrimState m) -> ByteCount -> m ()
forall (q :: * -> *) (m :: * -> *) a.
(WriteMem q m, Prim a, PrimUnaligned a) =>
a -> q (PrimState m) -> ByteCount -> m ()
writeMemInBytes DoubleBE
x) PutEff q m () -> PutEff q m a -> PutEff q m a
forall a b. PutEff q m a -> PutEff q m b -> PutEff q m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> PutEff q m a
k
PutFShortByteString ByteCount
bc ShortByteString
sbs PutEff q m a
k ->
ByteCount
-> (q (PrimState m) -> ByteCount -> m ()) -> PutEff q m ()
forall (m :: * -> *) (q :: * -> *).
PrimMonad m =>
ByteCount
-> (q (PrimState m) -> ByteCount -> m ()) -> PutEff q m ()
writeBytes ByteCount
bc (ShortByteString
-> ByteCount -> q (PrimState m) -> ByteCount -> m ()
forall (q :: * -> *) (m :: * -> *).
WriteMem q m =>
ShortByteString
-> ByteCount -> q (PrimState m) -> ByteCount -> m ()
writeSBSMem ShortByteString
sbs ByteCount
bc) PutEff q m () -> PutEff q m a -> PutEff q m a
forall a b. PutEff q m a -> PutEff q m b -> PutEff q m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> PutEff q m a
k
PutFStaticSeq PutStaticSeqF (PutEff q m a)
pss -> PutStaticSeqF (PutEff q m a) -> PutEff q m a
forall (q :: * -> *) (m :: * -> *) a.
WriteMem q m =>
PutStaticSeqF (PutEff q m a) -> PutEff q m a
writeStaticSeq PutStaticSeqF (PutEff q m a)
pss
PutFStaticArray PutStaticArrayF (PutEff q m a)
psa -> PutStaticArrayF (PutEff q m a) -> PutEff q m a
forall (q :: * -> *) (m :: * -> *) a.
WriteMem q m =>
PutStaticArrayF (PutEff q m a) -> PutEff q m a
writeStaticArray PutStaticArrayF (PutEff q m a)
psa
PutFByteArray ByteCount
bc ByteArray
barr PutEff q m a
k ->
ByteCount
-> (q (PrimState m) -> ByteCount -> m ()) -> PutEff q m ()
forall (m :: * -> *) (q :: * -> *).
PrimMonad m =>
ByteCount
-> (q (PrimState m) -> ByteCount -> m ()) -> PutEff q m ()
writeBytes ByteCount
bc (ByteArray
-> ByteCount -> ByteCount -> q (PrimState m) -> ByteCount -> m ()
forall (q :: * -> *) (m :: * -> *).
WriteMem q m =>
ByteArray
-> ByteCount -> ByteCount -> q (PrimState m) -> ByteCount -> m ()
copyArrayMemInBytes ByteArray
barr ByteCount
0 ByteCount
bc) PutEff q m () -> PutEff q m a -> PutEff q m a
forall a b. PutEff q m a -> PutEff q m b -> PutEff q m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> PutEff q m a
k
PutFStaticHint (PutStaticHintF ByteCount
_ Put
p PutEff q m a
k) -> Put -> PutEff q m ()
forall (q :: * -> *) (m :: * -> *) a.
WriteMem q m =>
PutM a -> PutEff q m a
mkPutEff Put
p PutEff q m () -> PutEff q m a -> PutEff q m a
forall a b. PutEff q m a -> PutEff q m b -> PutEff q m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> PutEff q m a
k
runPutRun :: (WriteMem q m) => PutRun q m a -> PutEnv (PrimState m) q -> m a
runPutRun :: forall (q :: * -> *) (m :: * -> *) a.
WriteMem q m =>
PutRun q m a -> PutEnv (PrimState m) q -> m a
runPutRun = PutEff q m a -> PutEnv (PrimState m) q -> m a
forall (q :: * -> *) (m :: * -> *) a.
PutEff q m a -> PutEnv (PrimState m) q -> m a
runPutEff (PutEff q m a -> PutEnv (PrimState m) q -> m a)
-> (PutRun q m a -> PutEff q m a)
-> PutRun q m a
-> PutEnv (PrimState m) q
-> m a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PutRun q m a -> PutEff q m a
forall (q :: * -> *) (m :: * -> *) a.
WriteMem q m =>
PutRun q m a -> PutEff q m a
iterPutRun
iterPutRun :: (WriteMem q m) => PutRun q m a -> PutEff q m a
iterPutRun :: forall (q :: * -> *) (m :: * -> *) a.
WriteMem q m =>
PutRun q m a -> PutEff q m a
iterPutRun PutRun q m a
act = (PutF (PutEff q m a) -> PutEff q m a)
-> FT PutF (PutEff q m) a -> PutEff q m a
forall (f :: * -> *) (m :: * -> *) a.
(Functor f, Monad m) =>
(f (m a) -> m a) -> FT f m a -> m a
iterT PutF (PutEff q m a) -> PutEff q m a
forall (q :: * -> *) (m :: * -> *) a.
WriteMem q m =>
PutF (PutEff q m a) -> PutEff q m a
execPutRun (PutRun q m a -> FT PutF (PutEff q m) a
forall (q :: * -> *) (m :: * -> *) a.
PutRun q m a -> FT PutF (PutEff q m) a
unPutRun PutRun q m a
act)
mkPutRun :: PutM a -> PutRun q m a
mkPutRun :: forall a (q :: * -> *) (m :: * -> *). PutM a -> PutRun q m a
mkPutRun (PutM (F forall r. (a -> r) -> (PutF r -> r) -> r
w)) = FT PutF (PutEff q m) a -> PutRun q m a
forall (q :: * -> *) (m :: * -> *) a.
FT PutF (PutEff q m) a -> PutRun q m a
PutRun ((a -> FT PutF (PutEff q m) a)
-> (PutF (FT PutF (PutEff q m) a) -> FT PutF (PutEff q m) a)
-> FT PutF (PutEff q m) a
forall r. (a -> r) -> (PutF r -> r) -> r
w a -> FT PutF (PutEff q m) a
forall a. a -> FT PutF (PutEff q m) a
forall (f :: * -> *) a. Applicative f => a -> f a
pure PutF (FT PutF (PutEff q m) a) -> FT PutF (PutEff q m) a
forall a. PutF (FT PutF (PutEff q m) a) -> FT PutF (PutEff q m) a
forall (f :: * -> *) (m :: * -> *) a.
MonadFree f m =>
f (m a) -> m a
wrap)
mkPutEff :: (WriteMem q m) => PutM a -> PutEff q m a
mkPutEff :: forall (q :: * -> *) (m :: * -> *) a.
WriteMem q m =>
PutM a -> PutEff q m a
mkPutEff = PutRun q m a -> PutEff q m a
forall (q :: * -> *) (m :: * -> *) a.
WriteMem q m =>
PutRun q m a -> PutEff q m a
iterPutRun (PutRun q m a -> PutEff q m a)
-> (PutM a -> PutRun q m a) -> PutM a -> PutEff q m a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PutM a -> PutRun q m a
forall a (q :: * -> *) (m :: * -> *). PutM a -> PutRun q m a
mkPutRun
runPutInternal :: (WriteMem q m) => ByteCount -> Put -> ByteCount -> q (PrimState m) -> m ByteCount
runPutInternal :: forall (q :: * -> *) (m :: * -> *).
WriteMem q m =>
ByteCount -> Put -> ByteCount -> q (PrimState m) -> m ByteCount
runPutInternal ByteCount
off Put
act ByteCount
len q (PrimState m)
mem = do
let eff :: PutRun q m ()
eff = Put -> PutRun q m ()
forall a (q :: * -> *) (m :: * -> *). PutM a -> PutRun q m a
mkPutRun Put
act
cap :: ByteCount
cap = ByteCount
off ByteCount -> ByteCount -> ByteCount
forall a. Num a => a -> a -> a
+ ByteCount
len
st :: PutEnv (PrimState m) q
st@(PutEnv MutVar (PrimState m) ByteCount
offRef ByteCount
_ q (PrimState m)
_) <- ByteCount
-> ByteCount -> q (PrimState m) -> m (PutEnv (PrimState m) q)
forall (m :: * -> *) (q :: * -> *).
PrimMonad m =>
ByteCount
-> ByteCount -> q (PrimState m) -> m (PutEnv (PrimState m) q)
newPutEnv ByteCount
off ByteCount
cap q (PrimState m)
mem
PutRun q m () -> PutEnv (PrimState m) q -> m ()
forall (q :: * -> *) (m :: * -> *) a.
WriteMem q m =>
PutRun q m a -> PutEnv (PrimState m) q -> m a
runPutRun PutRun q m ()
eff PutEnv (PrimState m) q
st
MutVar (PrimState m) ByteCount -> m ByteCount
forall (m :: * -> *) a.
PrimMonad m =>
MutVar (PrimState m) a -> m a
readMutVar MutVar (PrimState m) ByteCount
offRef
newtype CountEff a = CountEff {forall a. CountEff a -> MaybeT (State ByteCount) a
unCountEff :: MaybeT (State ByteCount) a}
deriving newtype ((forall a b. (a -> b) -> CountEff a -> CountEff b)
-> (forall a b. a -> CountEff b -> CountEff a) -> Functor CountEff
forall a b. a -> CountEff b -> CountEff a
forall a b. (a -> b) -> CountEff a -> CountEff b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
$cfmap :: forall a b. (a -> b) -> CountEff a -> CountEff b
fmap :: forall a b. (a -> b) -> CountEff a -> CountEff b
$c<$ :: forall a b. a -> CountEff b -> CountEff a
<$ :: forall a b. a -> CountEff b -> CountEff a
Functor, Functor CountEff
Functor CountEff =>
(forall a. a -> CountEff a)
-> (forall a b. CountEff (a -> b) -> CountEff a -> CountEff b)
-> (forall a b c.
(a -> b -> c) -> CountEff a -> CountEff b -> CountEff c)
-> (forall a b. CountEff a -> CountEff b -> CountEff b)
-> (forall a b. CountEff a -> CountEff b -> CountEff a)
-> Applicative CountEff
forall a. a -> CountEff a
forall a b. CountEff a -> CountEff b -> CountEff a
forall a b. CountEff a -> CountEff b -> CountEff b
forall a b. CountEff (a -> b) -> CountEff a -> CountEff b
forall a b c.
(a -> b -> c) -> CountEff a -> CountEff b -> CountEff c
forall (f :: * -> *).
Functor f =>
(forall a. a -> f a)
-> (forall a b. f (a -> b) -> f a -> f b)
-> (forall a b c. (a -> b -> c) -> f a -> f b -> f c)
-> (forall a b. f a -> f b -> f b)
-> (forall a b. f a -> f b -> f a)
-> Applicative f
$cpure :: forall a. a -> CountEff a
pure :: forall a. a -> CountEff a
$c<*> :: forall a b. CountEff (a -> b) -> CountEff a -> CountEff b
<*> :: forall a b. CountEff (a -> b) -> CountEff a -> CountEff b
$cliftA2 :: forall a b c.
(a -> b -> c) -> CountEff a -> CountEff b -> CountEff c
liftA2 :: forall a b c.
(a -> b -> c) -> CountEff a -> CountEff b -> CountEff c
$c*> :: forall a b. CountEff a -> CountEff b -> CountEff b
*> :: forall a b. CountEff a -> CountEff b -> CountEff b
$c<* :: forall a b. CountEff a -> CountEff b -> CountEff a
<* :: forall a b. CountEff a -> CountEff b -> CountEff a
Applicative, Applicative CountEff
Applicative CountEff =>
(forall a b. CountEff a -> (a -> CountEff b) -> CountEff b)
-> (forall a b. CountEff a -> CountEff b -> CountEff b)
-> (forall a. a -> CountEff a)
-> Monad CountEff
forall a. a -> CountEff a
forall a b. CountEff a -> CountEff b -> CountEff b
forall a b. CountEff a -> (a -> CountEff b) -> CountEff b
forall (m :: * -> *).
Applicative m =>
(forall a b. m a -> (a -> m b) -> m b)
-> (forall a b. m a -> m b -> m b)
-> (forall a. a -> m a)
-> Monad m
$c>>= :: forall a b. CountEff a -> (a -> CountEff b) -> CountEff b
>>= :: forall a b. CountEff a -> (a -> CountEff b) -> CountEff b
$c>> :: forall a b. CountEff a -> CountEff b -> CountEff b
>> :: forall a b. CountEff a -> CountEff b -> CountEff b
$creturn :: forall a. a -> CountEff a
return :: forall a. a -> CountEff a
Monad, Applicative CountEff
Applicative CountEff =>
(forall a. CountEff a)
-> (forall a. CountEff a -> CountEff a -> CountEff a)
-> (forall a. CountEff a -> CountEff [a])
-> (forall a. CountEff a -> CountEff [a])
-> Alternative CountEff
forall a. CountEff a
forall a. CountEff a -> CountEff [a]
forall a. CountEff a -> CountEff a -> CountEff a
forall (f :: * -> *).
Applicative f =>
(forall a. f a)
-> (forall a. f a -> f a -> f a)
-> (forall a. f a -> f [a])
-> (forall a. f a -> f [a])
-> Alternative f
$cempty :: forall a. CountEff a
empty :: forall a. CountEff a
$c<|> :: forall a. CountEff a -> CountEff a -> CountEff a
<|> :: forall a. CountEff a -> CountEff a -> CountEff a
$csome :: forall a. CountEff a -> CountEff [a]
some :: forall a. CountEff a -> CountEff [a]
$cmany :: forall a. CountEff a -> CountEff [a]
many :: forall a. CountEff a -> CountEff [a]
Alternative, MonadState ByteCount)
runCountEff :: CountEff a -> ByteCount -> (Maybe a, ByteCount)
runCountEff :: forall a. CountEff a -> ByteCount -> (Maybe a, ByteCount)
runCountEff CountEff a
act = State ByteCount (Maybe a) -> ByteCount -> (Maybe a, ByteCount)
forall s a. State s a -> s -> (a, s)
runState (MaybeT (State ByteCount) a -> State ByteCount (Maybe a)
forall (m :: * -> *) a. MaybeT m a -> m (Maybe a)
runMaybeT (CountEff a -> MaybeT (State ByteCount) a
forall a. CountEff a -> MaybeT (State ByteCount) a
unCountEff CountEff a
act))
newtype CountRun a = CountRun {forall a. CountRun a -> FT PutF CountEff a
unCountRun :: FT PutF CountEff a}
deriving newtype ((forall a b. (a -> b) -> CountRun a -> CountRun b)
-> (forall a b. a -> CountRun b -> CountRun a) -> Functor CountRun
forall a b. a -> CountRun b -> CountRun a
forall a b. (a -> b) -> CountRun a -> CountRun b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
$cfmap :: forall a b. (a -> b) -> CountRun a -> CountRun b
fmap :: forall a b. (a -> b) -> CountRun a -> CountRun b
$c<$ :: forall a b. a -> CountRun b -> CountRun a
<$ :: forall a b. a -> CountRun b -> CountRun a
Functor, Functor CountRun
Functor CountRun =>
(forall a. a -> CountRun a)
-> (forall a b. CountRun (a -> b) -> CountRun a -> CountRun b)
-> (forall a b c.
(a -> b -> c) -> CountRun a -> CountRun b -> CountRun c)
-> (forall a b. CountRun a -> CountRun b -> CountRun b)
-> (forall a b. CountRun a -> CountRun b -> CountRun a)
-> Applicative CountRun
forall a. a -> CountRun a
forall a b. CountRun a -> CountRun b -> CountRun a
forall a b. CountRun a -> CountRun b -> CountRun b
forall a b. CountRun (a -> b) -> CountRun a -> CountRun b
forall a b c.
(a -> b -> c) -> CountRun a -> CountRun b -> CountRun c
forall (f :: * -> *).
Functor f =>
(forall a. a -> f a)
-> (forall a b. f (a -> b) -> f a -> f b)
-> (forall a b c. (a -> b -> c) -> f a -> f b -> f c)
-> (forall a b. f a -> f b -> f b)
-> (forall a b. f a -> f b -> f a)
-> Applicative f
$cpure :: forall a. a -> CountRun a
pure :: forall a. a -> CountRun a
$c<*> :: forall a b. CountRun (a -> b) -> CountRun a -> CountRun b
<*> :: forall a b. CountRun (a -> b) -> CountRun a -> CountRun b
$cliftA2 :: forall a b c.
(a -> b -> c) -> CountRun a -> CountRun b -> CountRun c
liftA2 :: forall a b c.
(a -> b -> c) -> CountRun a -> CountRun b -> CountRun c
$c*> :: forall a b. CountRun a -> CountRun b -> CountRun b
*> :: forall a b. CountRun a -> CountRun b -> CountRun b
$c<* :: forall a b. CountRun a -> CountRun b -> CountRun a
<* :: forall a b. CountRun a -> CountRun b -> CountRun a
Applicative, Applicative CountRun
Applicative CountRun =>
(forall a b. CountRun a -> (a -> CountRun b) -> CountRun b)
-> (forall a b. CountRun a -> CountRun b -> CountRun b)
-> (forall a. a -> CountRun a)
-> Monad CountRun
forall a. a -> CountRun a
forall a b. CountRun a -> CountRun b -> CountRun b
forall a b. CountRun a -> (a -> CountRun b) -> CountRun b
forall (m :: * -> *).
Applicative m =>
(forall a b. m a -> (a -> m b) -> m b)
-> (forall a b. m a -> m b -> m b)
-> (forall a. a -> m a)
-> Monad m
$c>>= :: forall a b. CountRun a -> (a -> CountRun b) -> CountRun b
>>= :: forall a b. CountRun a -> (a -> CountRun b) -> CountRun b
$c>> :: forall a b. CountRun a -> CountRun b -> CountRun b
>> :: forall a b. CountRun a -> CountRun b -> CountRun b
$creturn :: forall a. a -> CountRun a
return :: forall a. a -> CountRun a
Monad)
execCountRun :: PutF (CountEff a) -> CountEff a
execCountRun :: forall a. PutF (CountEff a) -> CountEff a
execCountRun = \case
PutFWord8 Word8
_ CountEff a
k -> (ByteCount -> ByteCount) -> CountEff ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
State.modify' (ByteCount
1 ByteCount -> ByteCount -> ByteCount
forall a. Num a => a -> a -> a
+) CountEff () -> CountEff a -> CountEff a
forall a b. CountEff a -> CountEff b -> CountEff b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> CountEff a
k
PutFInt8 Int8
_ CountEff a
k -> (ByteCount -> ByteCount) -> CountEff ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
State.modify' (ByteCount
1 ByteCount -> ByteCount -> ByteCount
forall a. Num a => a -> a -> a
+) CountEff () -> CountEff a -> CountEff a
forall a b. CountEff a -> CountEff b -> CountEff b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> CountEff a
k
PutFWord16LE Word16LE
_ CountEff a
k -> (ByteCount -> ByteCount) -> CountEff ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
State.modify' (ByteCount
2 ByteCount -> ByteCount -> ByteCount
forall a. Num a => a -> a -> a
+) CountEff () -> CountEff a -> CountEff a
forall a b. CountEff a -> CountEff b -> CountEff b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> CountEff a
k
PutFInt16LE Int16LE
_ CountEff a
k -> (ByteCount -> ByteCount) -> CountEff ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
State.modify' (ByteCount
2 ByteCount -> ByteCount -> ByteCount
forall a. Num a => a -> a -> a
+) CountEff () -> CountEff a -> CountEff a
forall a b. CountEff a -> CountEff b -> CountEff b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> CountEff a
k
PutFWord24LE Word24LE
_ CountEff a
k -> (ByteCount -> ByteCount) -> CountEff ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
State.modify' (ByteCount
3 ByteCount -> ByteCount -> ByteCount
forall a. Num a => a -> a -> a
+) CountEff () -> CountEff a -> CountEff a
forall a b. CountEff a -> CountEff b -> CountEff b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> CountEff a
k
PutFInt24LE Int24LE
_ CountEff a
k -> (ByteCount -> ByteCount) -> CountEff ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
State.modify' (ByteCount
3 ByteCount -> ByteCount -> ByteCount
forall a. Num a => a -> a -> a
+) CountEff () -> CountEff a -> CountEff a
forall a b. CountEff a -> CountEff b -> CountEff b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> CountEff a
k
PutFWord32LE Word32LE
_ CountEff a
k -> (ByteCount -> ByteCount) -> CountEff ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
State.modify' (ByteCount
4 ByteCount -> ByteCount -> ByteCount
forall a. Num a => a -> a -> a
+) CountEff () -> CountEff a -> CountEff a
forall a b. CountEff a -> CountEff b -> CountEff b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> CountEff a
k
PutFInt32LE Int32LE
_ CountEff a
k -> (ByteCount -> ByteCount) -> CountEff ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
State.modify' (ByteCount
4 ByteCount -> ByteCount -> ByteCount
forall a. Num a => a -> a -> a
+) CountEff () -> CountEff a -> CountEff a
forall a b. CountEff a -> CountEff b -> CountEff b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> CountEff a
k
PutFWord64LE Word64LE
_ CountEff a
k -> (ByteCount -> ByteCount) -> CountEff ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
State.modify' (ByteCount
8 ByteCount -> ByteCount -> ByteCount
forall a. Num a => a -> a -> a
+) CountEff () -> CountEff a -> CountEff a
forall a b. CountEff a -> CountEff b -> CountEff b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> CountEff a
k
PutFInt64LE Int64LE
_ CountEff a
k -> (ByteCount -> ByteCount) -> CountEff ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
State.modify' (ByteCount
8 ByteCount -> ByteCount -> ByteCount
forall a. Num a => a -> a -> a
+) CountEff () -> CountEff a -> CountEff a
forall a b. CountEff a -> CountEff b -> CountEff b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> CountEff a
k
PutFFloatLE FloatLE
_ CountEff a
k -> (ByteCount -> ByteCount) -> CountEff ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
State.modify' (ByteCount
4 ByteCount -> ByteCount -> ByteCount
forall a. Num a => a -> a -> a
+) CountEff () -> CountEff a -> CountEff a
forall a b. CountEff a -> CountEff b -> CountEff b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> CountEff a
k
PutFDoubleLE DoubleLE
_ CountEff a
k -> (ByteCount -> ByteCount) -> CountEff ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
State.modify' (ByteCount
8 ByteCount -> ByteCount -> ByteCount
forall a. Num a => a -> a -> a
+) CountEff () -> CountEff a -> CountEff a
forall a b. CountEff a -> CountEff b -> CountEff b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> CountEff a
k
PutFWord16BE Word16BE
_ CountEff a
k -> (ByteCount -> ByteCount) -> CountEff ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
State.modify' (ByteCount
2 ByteCount -> ByteCount -> ByteCount
forall a. Num a => a -> a -> a
+) CountEff () -> CountEff a -> CountEff a
forall a b. CountEff a -> CountEff b -> CountEff b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> CountEff a
k
PutFInt16BE Int16BE
_ CountEff a
k -> (ByteCount -> ByteCount) -> CountEff ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
State.modify' (ByteCount
2 ByteCount -> ByteCount -> ByteCount
forall a. Num a => a -> a -> a
+) CountEff () -> CountEff a -> CountEff a
forall a b. CountEff a -> CountEff b -> CountEff b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> CountEff a
k
PutFWord24BE Word24BE
_ CountEff a
k -> (ByteCount -> ByteCount) -> CountEff ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
State.modify' (ByteCount
3 ByteCount -> ByteCount -> ByteCount
forall a. Num a => a -> a -> a
+) CountEff () -> CountEff a -> CountEff a
forall a b. CountEff a -> CountEff b -> CountEff b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> CountEff a
k
PutFInt24BE Int24BE
_ CountEff a
k -> (ByteCount -> ByteCount) -> CountEff ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
State.modify' (ByteCount
3 ByteCount -> ByteCount -> ByteCount
forall a. Num a => a -> a -> a
+) CountEff () -> CountEff a -> CountEff a
forall a b. CountEff a -> CountEff b -> CountEff b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> CountEff a
k
PutFWord32BE Word32BE
_ CountEff a
k -> (ByteCount -> ByteCount) -> CountEff ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
State.modify' (ByteCount
4 ByteCount -> ByteCount -> ByteCount
forall a. Num a => a -> a -> a
+) CountEff () -> CountEff a -> CountEff a
forall a b. CountEff a -> CountEff b -> CountEff b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> CountEff a
k
PutFInt32BE Int32BE
_ CountEff a
k -> (ByteCount -> ByteCount) -> CountEff ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
State.modify' (ByteCount
4 ByteCount -> ByteCount -> ByteCount
forall a. Num a => a -> a -> a
+) CountEff () -> CountEff a -> CountEff a
forall a b. CountEff a -> CountEff b -> CountEff b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> CountEff a
k
PutFWord64BE Word64BE
_ CountEff a
k -> (ByteCount -> ByteCount) -> CountEff ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
State.modify' (ByteCount
8 ByteCount -> ByteCount -> ByteCount
forall a. Num a => a -> a -> a
+) CountEff () -> CountEff a -> CountEff a
forall a b. CountEff a -> CountEff b -> CountEff b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> CountEff a
k
PutFInt64BE Int64BE
_ CountEff a
k -> (ByteCount -> ByteCount) -> CountEff ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
State.modify' (ByteCount
8 ByteCount -> ByteCount -> ByteCount
forall a. Num a => a -> a -> a
+) CountEff () -> CountEff a -> CountEff a
forall a b. CountEff a -> CountEff b -> CountEff b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> CountEff a
k
PutFFloatBE FloatBE
_ CountEff a
k -> (ByteCount -> ByteCount) -> CountEff ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
State.modify' (ByteCount
4 ByteCount -> ByteCount -> ByteCount
forall a. Num a => a -> a -> a
+) CountEff () -> CountEff a -> CountEff a
forall a b. CountEff a -> CountEff b -> CountEff b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> CountEff a
k
PutFDoubleBE DoubleBE
_ CountEff a
k -> (ByteCount -> ByteCount) -> CountEff ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
State.modify' (ByteCount
8 ByteCount -> ByteCount -> ByteCount
forall a. Num a => a -> a -> a
+) CountEff () -> CountEff a -> CountEff a
forall a b. CountEff a -> CountEff b -> CountEff b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> CountEff a
k
PutFShortByteString ByteCount
bc ShortByteString
_ CountEff a
k -> (ByteCount -> ByteCount) -> CountEff ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
State.modify' (ByteCount
bc ByteCount -> ByteCount -> ByteCount
forall a. Num a => a -> a -> a
+) CountEff () -> CountEff a -> CountEff a
forall a b. CountEff a -> CountEff b -> CountEff b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> CountEff a
k
PutFStaticSeq pss :: PutStaticSeqF (CountEff a)
pss@(PutStaticSeqF ElemCount
_ Maybe z
_ z -> Put
_ Seq z
_ CountEff a
k) ->
let bc :: ByteCount
bc = PutStaticSeqF (CountEff a) -> ByteCount
forall a. PutStaticSeqF a -> ByteCount
putStaticSeqSize PutStaticSeqF (CountEff a)
pss
in (ByteCount -> ByteCount) -> CountEff ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
State.modify' (ByteCount
bc ByteCount -> ByteCount -> ByteCount
forall a. Num a => a -> a -> a
+) CountEff () -> CountEff a -> CountEff a
forall a b. CountEff a -> CountEff b -> CountEff b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> CountEff a
k
PutFStaticArray psv :: PutStaticArrayF (CountEff a)
psv@(PutStaticArrayF ElemCount
_ Maybe z
_ PrimArray z
_ CountEff a
k) ->
let bc :: ByteCount
bc = PutStaticArrayF (CountEff a) -> ByteCount
forall a. PutStaticArrayF a -> ByteCount
putStaticArraySize PutStaticArrayF (CountEff a)
psv
in (ByteCount -> ByteCount) -> CountEff ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
State.modify' (ByteCount
bc ByteCount -> ByteCount -> ByteCount
forall a. Num a => a -> a -> a
+) CountEff () -> CountEff a -> CountEff a
forall a b. CountEff a -> CountEff b -> CountEff b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> CountEff a
k
PutFByteArray ByteCount
bc ByteArray
_ CountEff a
k -> (ByteCount -> ByteCount) -> CountEff ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
State.modify' (ByteCount
bc ByteCount -> ByteCount -> ByteCount
forall a. Num a => a -> a -> a
+) CountEff () -> CountEff a -> CountEff a
forall a b. CountEff a -> CountEff b -> CountEff b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> CountEff a
k
PutFStaticHint (PutStaticHintF ByteCount
bc Put
_ CountEff a
k) -> (ByteCount -> ByteCount) -> CountEff ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
State.modify' (ByteCount
bc ByteCount -> ByteCount -> ByteCount
forall a. Num a => a -> a -> a
+) CountEff () -> CountEff a -> CountEff a
forall a b. CountEff a -> CountEff b -> CountEff b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> CountEff a
k
runCountRun :: CountRun a -> ByteCount -> (Maybe a, ByteCount)
runCountRun :: forall a. CountRun a -> ByteCount -> (Maybe a, ByteCount)
runCountRun = CountEff a -> ByteCount -> (Maybe a, ByteCount)
forall a. CountEff a -> ByteCount -> (Maybe a, ByteCount)
runCountEff (CountEff a -> ByteCount -> (Maybe a, ByteCount))
-> (CountRun a -> CountEff a)
-> CountRun a
-> ByteCount
-> (Maybe a, ByteCount)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CountRun a -> CountEff a
forall a. CountRun a -> CountEff a
iterCountRun
iterCountRun :: CountRun a -> CountEff a
iterCountRun :: forall a. CountRun a -> CountEff a
iterCountRun CountRun a
act = (PutF (CountEff a) -> CountEff a)
-> FT PutF CountEff a -> CountEff a
forall (f :: * -> *) (m :: * -> *) a.
(Functor f, Monad m) =>
(f (m a) -> m a) -> FT f m a -> m a
iterT PutF (CountEff a) -> CountEff a
forall a. PutF (CountEff a) -> CountEff a
execCountRun (CountRun a -> FT PutF CountEff a
forall a. CountRun a -> FT PutF CountEff a
unCountRun CountRun a
act)
mkCountRun :: PutM a -> CountRun a
mkCountRun :: forall a. PutM a -> CountRun a
mkCountRun (PutM (F forall r. (a -> r) -> (PutF r -> r) -> r
w)) = FT PutF CountEff a -> CountRun a
forall a. FT PutF CountEff a -> CountRun a
CountRun ((a -> FT PutF CountEff a)
-> (PutF (FT PutF CountEff a) -> FT PutF CountEff a)
-> FT PutF CountEff a
forall r. (a -> r) -> (PutF r -> r) -> r
w a -> FT PutF CountEff a
forall a. a -> FT PutF CountEff a
forall (f :: * -> *) a. Applicative f => a -> f a
pure PutF (FT PutF CountEff a) -> FT PutF CountEff a
forall a. PutF (FT PutF CountEff a) -> FT PutF CountEff a
forall (f :: * -> *) (m :: * -> *) a.
MonadFree f m =>
f (m a) -> m a
wrap)
mkCountEff :: PutM a -> CountEff a
mkCountEff :: forall a. PutM a -> CountEff a
mkCountEff = CountRun a -> CountEff a
forall a. CountRun a -> CountEff a
iterCountRun (CountRun a -> CountEff a)
-> (PutM a -> CountRun a) -> PutM a -> CountEff a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PutM a -> CountRun a
forall a. PutM a -> CountRun a
mkCountRun
runCount :: Put -> ByteCount
runCount :: Put -> ByteCount
runCount Put
act =
let eff :: CountRun ()
eff = Put -> CountRun ()
forall a. PutM a -> CountRun a
mkCountRun Put
act
(Maybe ()
_, ByteCount
bc) = CountRun () -> ByteCount -> (Maybe (), ByteCount)
forall a. CountRun a -> ByteCount -> (Maybe a, ByteCount)
runCountRun CountRun ()
eff ByteCount
0
in ByteCount
bc