{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveFunctor #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE MagicHash #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RankNTypes#-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE ViewPatterns #-}
{-# LANGUAGE EmptyCase #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}
module Data.Store.Internal
    (
    
      encode,
      decode, decodeWith,
      decodeEx, decodeExWith, decodeExPortionWith
    , decodeIO, decodeIOWith, decodeIOPortionWith
    
    , Store(..), Poke, Peek, runPeek
    
    , PokeException(..), pokeException
    
    , PeekException(..), peekException, tooManyBytes
    
    , Size(..)
    , getSize, getSizeWith
    , combineSize, combineSizeWith, addSize
    
    , sizeSequence, pokeSequence, peekSequence
    
    , sizeSet, pokeSet, peekSet
    
    , sizeMap, pokeMap, peekMap
    
    , sizeOrdMap, pokeOrdMap, peekOrdMapWith
    
    , sizeArray, pokeArray, peekArray
    
    , GStoreSize, genericSize
    , GStorePoke, genericPoke
    , GStorePeek, genericPeek
    
    , skip, isolate
    , peekMagic
    
    
    
    
    
    , IsStaticSize(..), StaticSize(..), toStaticSizeEx, liftStaticSize, staticByteStringExp
    ) where
import           Control.Applicative
import           Control.DeepSeq (NFData)
import           Control.Exception (throwIO)
import           Control.Monad (when)
import           Control.Monad.IO.Class (liftIO)
import qualified Data.Array.Unboxed as A
import qualified Data.ByteString as BS
import qualified Data.ByteString.Internal as BS
import qualified Data.ByteString.Lazy as LBS
import qualified Data.ByteString.Short.Internal as SBS
import           Data.Containers (IsMap, ContainerKey, MapValue, mapFromList, mapToList, IsSet, setFromList)
import           Data.Complex (Complex (..))
import           Data.Data (Data)
import           Data.Fixed (Fixed (..), Pico)
import           Data.Foldable (forM_, foldl')
import           Data.Functor.Contravariant
import           Data.Functor.Identity (Identity (..))
import           Data.HashMap.Strict (HashMap)
import           Data.HashSet (HashSet)
import           Data.Hashable (Hashable)
import           Data.Int
import           Data.IntMap (IntMap)
import qualified Data.IntMap.Strict as IntMap
import           Data.IntSet (IntSet)
import qualified Data.IntSet as IntSet
import qualified Data.List.NonEmpty as NE
import           Data.Map (Map)
import qualified Data.Map.Strict as Map
import           Data.MonoTraversable
import           Data.Monoid
import           Data.Orphans ()
import           Data.Primitive.ByteArray
import           Data.Proxy (Proxy(..))
import           Data.Sequence (Seq)
import           Data.Sequences (IsSequence, Index, replicateM)
import           Data.Set (Set)
import qualified Data.Set as Set
import           Data.Store.Impl
import           Data.Store.Core
import           Data.Store.TH.Internal
import qualified Data.Text as T
import qualified Data.Text.Array as TA
import qualified Data.Text.Foreign as T
import qualified Data.Text.Internal as T
import qualified Data.Time as Time
import qualified Data.Time.Clock.TAI as Time
import           Data.Typeable (Typeable)
import qualified Data.Vector as V
import qualified Data.Vector.Mutable as MV
import qualified Data.Vector.Storable as SV
import qualified Data.Vector.Storable.Mutable as MSV
import qualified Data.Vector.Unboxed as UV
#if MIN_VERSION_vector(0,13,2)
import qualified Data.Vector.Strict as SCV
import qualified Data.Vector.Strict.Mutable as MSCV
#endif
import           Data.Void
import           Data.Word
import           Foreign.C.Types ()
import           Foreign.Ptr (plusPtr, minusPtr)
import           Foreign.Storable (Storable, sizeOf)
import           GHC.Generics (Generic)
import           GHC.Real (Ratio(..))
import           GHC.TypeLits
import           Instances.TH.Lift ()
import           Language.Haskell.TH
import           Language.Haskell.TH.Instances ()
import           Language.Haskell.TH.ReifyMany
import           Language.Haskell.TH.Syntax
import           Network.Socket (AddrInfo)
import           Numeric.Natural (Natural)
import           Prelude
import           TH.Derive
#if MIN_VERSION_time(1,8,0)
import qualified Data.Time.Clock.System as Time
#endif
#if MIN_VERSION_time(1,9,0)
import qualified Data.Time.Format.ISO8601 as Time
#endif
#if MIN_VERSION_time(1,11,0)
import qualified Data.Time.Calendar.Quarter as Time
import qualified Data.Time.Calendar.WeekDate as Time
#endif
#ifdef INTEGER_GMP
import qualified GHC.Integer.GMP.Internals as I
import           GHC.Types (Int (I#))
#else
import           GHC.Types (Word (W#))
import qualified GHC.Integer.Simple.Internals as I
#endif
#ifdef INTEGER_GMP
#if MIN_VERSION_integer_gmp(1,0,0)
import           GHC.Prim (sizeofByteArray#)
#endif
#endif
$(return $ map deriveTupleStoreInstance [2..7])
$(deriveManyStoreFromStorable
  (\ty ->
    case ty of
      ConT n | elem n [''Char, ''Int, ''Int64, ''Word, ''Word8, ''Word32] -> True
      _ -> False
    ))
sizeSequence :: forall t. (IsSequence t, Store (Element t)) => Size t
sizeSequence :: forall t. (IsSequence t, Store (Element t)) => Size t
sizeSequence = (t -> Int) -> Size t
forall a. (a -> Int) -> Size a
VarSize ((t -> Int) -> Size t) -> (t -> Int) -> Size t
forall a b. (a -> b) -> a -> b
$ \t
t ->
    case Size (Element t)
forall a. Store a => Size a
size :: Size (Element t) of
        ConstSize Int
n -> Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
* (t -> Int
forall mono. MonoFoldable mono => mono -> Int
olength t
t) Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int -> Int
forall a. Storable a => a -> Int
sizeOf (Int
forall a. HasCallStack => a
undefined :: Int)
        VarSize Element t -> Int
f -> (Int -> Element t -> Int) -> Int -> t -> Int
forall mono a.
MonoFoldable mono =>
(a -> Element mono -> a) -> a -> mono -> a
forall a. (a -> Element t -> a) -> a -> t -> a
ofoldl' (\Int
acc Element t
x -> Int
acc Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Element t -> Int
f Element t
x) (Int -> Int
forall a. Storable a => a -> Int
sizeOf (Int
forall a. HasCallStack => a
undefined :: Int)) t
t
{-# INLINE sizeSequence #-}
pokeSequence :: (IsSequence t, Store (Element t)) => t -> Poke ()
pokeSequence :: forall t. (IsSequence t, Store (Element t)) => t -> Poke ()
pokeSequence t
t =
  do Int -> Poke ()
forall a. Storable a => a -> Poke ()
pokeStorable Int
len
     (PokeState -> Int -> IO (Int, ())) -> Poke ()
forall a. (PokeState -> Int -> IO (Int, a)) -> Poke a
Poke (\PokeState
ptr Int
offset ->
             do Int
offset' <-
                  (Int -> Element t -> IO Int) -> Int -> t -> IO Int
forall mono (m :: * -> *) a.
(MonoFoldable mono, Monad m) =>
(a -> Element mono -> m a) -> a -> mono -> m a
forall (m :: * -> *) a.
Monad m =>
(a -> Element t -> m a) -> a -> t -> m a
ofoldlM (\Int
offset' Element t
a ->
                             do (Int
offset'',()
_) <- Poke () -> PokeState -> Int -> IO (Int, ())
forall a. Poke a -> PokeState -> Int -> IO (Int, a)
runPoke (Element t -> Poke ()
forall a. Store a => a -> Poke ()
poke Element t
a) PokeState
ptr Int
offset'
                                Int -> IO Int
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Int
offset'')
                          Int
offset
                          t
t
                (Int, ()) -> IO (Int, ())
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Int
offset',()))
  where len :: Int
len = t -> Int
forall mono. MonoFoldable mono => mono -> Int
olength t
t
{-# INLINE pokeSequence #-}
peekSequence :: (IsSequence t, Store (Element t), Index t ~ Int) => Peek t
peekSequence :: forall t.
(IsSequence t, Store (Element t), Index t ~ Int) =>
Peek t
peekSequence = do
    Int
len <- Peek Int
forall a. Store a => Peek a
peek
    Index t -> Peek (Element t) -> Peek t
forall seq (m :: * -> *).
(IsSequence seq, Monad m) =>
Index seq -> m (Element seq) -> m seq
forall (m :: * -> *). Monad m => Index t -> m (Element t) -> m t
replicateM Int
Index t
len Peek (Element t)
forall a. Store a => Peek a
peek
{-# INLINE peekSequence #-}
sizeSet :: forall t. (IsSet t, Store (Element t)) => Size t
sizeSet :: forall t. (IsSet t, Store (Element t)) => Size t
sizeSet = (t -> Int) -> Size t
forall a. (a -> Int) -> Size a
VarSize ((t -> Int) -> Size t) -> (t -> Int) -> Size t
forall a b. (a -> b) -> a -> b
$ \t
t ->
    case Size (Element t)
Size (ContainerKey t)
forall a. Store a => Size a
size :: Size (Element t) of
        ConstSize Int
n -> Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
* (t -> Int
forall mono. MonoFoldable mono => mono -> Int
olength t
t) Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int -> Int
forall a. Storable a => a -> Int
sizeOf (Int
forall a. HasCallStack => a
undefined :: Int)
        VarSize Element t -> Int
f -> (Int -> Element t -> Int) -> Int -> t -> Int
forall mono a.
MonoFoldable mono =>
(a -> Element mono -> a) -> a -> mono -> a
forall a. (a -> Element t -> a) -> a -> t -> a
ofoldl' (\Int
acc Element t
x -> Int
acc Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Element t -> Int
f Element t
x) (Int -> Int
forall a. Storable a => a -> Int
sizeOf (Int
forall a. HasCallStack => a
undefined :: Int)) t
t
{-# INLINE sizeSet #-}
pokeSet :: (IsSet t, Store (Element t)) => t -> Poke ()
pokeSet :: forall t. (IsSet t, Store (Element t)) => t -> Poke ()
pokeSet t
t = do
    Int -> Poke ()
forall a. Storable a => a -> Poke ()
pokeStorable (t -> Int
forall mono. MonoFoldable mono => mono -> Int
olength t
t)
    (Element t -> Poke ()) -> t -> Poke ()
forall mono (m :: * -> *).
(MonoFoldable mono, Applicative m) =>
(Element mono -> m ()) -> mono -> m ()
forall (m :: * -> *).
Applicative m =>
(Element t -> m ()) -> t -> m ()
omapM_ Element t -> Poke ()
ContainerKey t -> Poke ()
forall a. Store a => a -> Poke ()
poke t
t
{-# INLINE pokeSet #-}
peekSet :: (IsSet t, Store (Element t)) => Peek t
peekSet :: forall t. (IsSet t, Store (Element t)) => Peek t
peekSet = do
    Int
len <- Peek Int
forall a. Store a => Peek a
peek
    [Element t] -> t
[ContainerKey t] -> t
forall set. IsSet set => [Element set] -> set
setFromList ([ContainerKey t] -> t) -> Peek [ContainerKey t] -> Peek t
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Index [ContainerKey t]
-> Peek (Element [ContainerKey t]) -> Peek [ContainerKey t]
forall seq (m :: * -> *).
(IsSequence seq, Monad m) =>
Index seq -> m (Element seq) -> m seq
forall (m :: * -> *).
Monad m =>
Index [ContainerKey t]
-> m (Element [ContainerKey t]) -> m [ContainerKey t]
replicateM Int
Index [ContainerKey t]
len Peek (Element [ContainerKey t])
Peek (ContainerKey t)
forall a. Store a => Peek a
peek
{-# INLINE peekSet #-}
sizeMap
    :: forall t. (Store (ContainerKey t), Store (MapValue t), IsMap t)
    => Size t
sizeMap :: forall t.
(Store (ContainerKey t), Store (MapValue t), IsMap t) =>
Size t
sizeMap = (t -> Int) -> Size t
forall a. (a -> Int) -> Size a
VarSize ((t -> Int) -> Size t) -> (t -> Int) -> Size t
forall a b. (a -> b) -> a -> b
$ \t
t ->
    case (Size (ContainerKey t)
forall a. Store a => Size a
size :: Size (ContainerKey t), Size (MapValue t)
forall a. Store a => Size a
size :: Size (MapValue t)) of
        (ConstSize Int
nk, ConstSize Int
na) -> (Int
nk Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
na) Int -> Int -> Int
forall a. Num a => a -> a -> a
* t -> Int
forall mono. MonoFoldable mono => mono -> Int
olength t
t Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int -> Int
forall a. Storable a => a -> Int
sizeOf (Int
forall a. HasCallStack => a
undefined :: Int)
        (Size (ContainerKey t)
szk, Size (MapValue t)
sza) -> (Int -> Element [(ContainerKey t, MapValue t)] -> Int)
-> Int -> [(ContainerKey t, MapValue t)] -> Int
forall mono a.
MonoFoldable mono =>
(a -> Element mono -> a) -> a -> mono -> a
forall a.
(a -> Element [(ContainerKey t, MapValue t)] -> a)
-> a -> [(ContainerKey t, MapValue t)] -> a
ofoldl' (\Int
acc (ContainerKey t
k, MapValue t
a) -> Int
acc Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Size (ContainerKey t) -> ContainerKey t -> Int
forall a. Size a -> a -> Int
getSizeWith Size (ContainerKey t)
szk ContainerKey t
k Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Size (MapValue t) -> MapValue t -> Int
forall a. Size a -> a -> Int
getSizeWith Size (MapValue t)
sza MapValue t
a)
                              (Int -> Int
forall a. Storable a => a -> Int
sizeOf (Int
forall a. HasCallStack => a
undefined :: Int))
                              (t -> [(ContainerKey t, MapValue t)]
forall map. IsMap map => map -> [(ContainerKey map, MapValue map)]
mapToList t
t)
{-# INLINE sizeMap #-}
pokeMap
    :: (Store (ContainerKey t), Store (MapValue t), IsMap t)
    => t
    -> Poke ()
pokeMap :: forall t.
(Store (ContainerKey t), Store (MapValue t), IsMap t) =>
t -> Poke ()
pokeMap = [(ContainerKey t, MapValue t)] -> Poke ()
forall t. (IsSequence t, Store (Element t)) => t -> Poke ()
pokeSequence ([(ContainerKey t, MapValue t)] -> Poke ())
-> (t -> [(ContainerKey t, MapValue t)]) -> t -> Poke ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. t -> [(ContainerKey t, MapValue t)]
forall map. IsMap map => map -> [(ContainerKey map, MapValue map)]
mapToList
{-# INLINE pokeMap #-}
peekMap
    :: (Store (ContainerKey t), Store (MapValue t), IsMap t)
    => Peek t
peekMap :: forall t.
(Store (ContainerKey t), Store (MapValue t), IsMap t) =>
Peek t
peekMap = [(ContainerKey t, MapValue t)] -> t
forall map. IsMap map => [(ContainerKey map, MapValue map)] -> map
mapFromList ([(ContainerKey t, MapValue t)] -> t)
-> Peek [(ContainerKey t, MapValue t)] -> Peek t
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Peek [(ContainerKey t, MapValue t)]
forall a. Store a => Peek a
peek
{-# INLINE peekMap #-}
markMapPokedInAscendingOrder :: Word32
markMapPokedInAscendingOrder :: Word32
markMapPokedInAscendingOrder = Word32
1217678090
peekMagic
    :: (Eq a, Show a, Store a)
    => String -> a -> Peek ()
peekMagic :: forall a. (Eq a, Show a, Store a) => String -> a -> Peek ()
peekMagic String
markedThing a
x = do
    a
x' <- Peek a
forall a. Store a => Peek a
peek
    Bool -> Peek () -> Peek ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (a
x' a -> a -> Bool
forall a. Eq a => a -> a -> Bool
/= a
x) (Peek () -> Peek ()) -> Peek () -> Peek ()
forall a b. (a -> b) -> a -> b
$
        String -> Peek ()
forall a. String -> Peek a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String
"Expected marker for " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
markedThing String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
": " String -> String -> String
forall a. [a] -> [a] -> [a]
++ a -> String
forall a. Show a => a -> String
show a
x String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" but got: " String -> String -> String
forall a. [a] -> [a] -> [a]
++ a -> String
forall a. Show a => a -> String
show a
x')
{-# INLINE peekMagic #-}
sizeOrdMap
    :: forall t.
       (Store (ContainerKey t), Store (MapValue t), IsMap t)
    => Size t
sizeOrdMap :: forall t.
(Store (ContainerKey t), Store (MapValue t), IsMap t) =>
Size t
sizeOrdMap =
    (t -> Word32) -> (t -> t) -> Size Word32 -> Size t -> Size t
forall a b c. (c -> a) -> (c -> b) -> Size a -> Size b -> Size c
combineSizeWith (Word32 -> t -> Word32
forall a b. a -> b -> a
const Word32
markMapPokedInAscendingOrder) t -> t
forall a. a -> a
id Size Word32
forall a. Store a => Size a
size Size t
forall t.
(Store (ContainerKey t), Store (MapValue t), IsMap t) =>
Size t
sizeMap
{-# INLINE sizeOrdMap #-}
pokeOrdMap
    :: (Store (ContainerKey t), Store (MapValue t), IsMap t)
    => t -> Poke ()
pokeOrdMap :: forall t.
(Store (ContainerKey t), Store (MapValue t), IsMap t) =>
t -> Poke ()
pokeOrdMap t
x = Word32 -> Poke ()
forall a. Store a => a -> Poke ()
poke Word32
markMapPokedInAscendingOrder Poke () -> Poke () -> Poke ()
forall a b. Poke a -> Poke b -> Poke b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> t -> Poke ()
forall t.
(Store (ContainerKey t), Store (MapValue t), IsMap t) =>
t -> Poke ()
pokeMap t
x
{-# INLINE pokeOrdMap #-}
peekOrdMapWith
    :: (Store (ContainerKey t), Store (MapValue t))
    => ([(ContainerKey t, MapValue t)] -> t)
       
       
    -> Peek t
peekOrdMapWith :: forall t.
(Store (ContainerKey t), Store (MapValue t)) =>
([(ContainerKey t, MapValue t)] -> t) -> Peek t
peekOrdMapWith [(ContainerKey t, MapValue t)] -> t
f = do
    String -> Word32 -> Peek ()
forall a. (Eq a, Show a, Store a) => String -> a -> Peek ()
peekMagic String
"ascending Map / IntMap" Word32
markMapPokedInAscendingOrder
    [(ContainerKey t, MapValue t)] -> t
f ([(ContainerKey t, MapValue t)] -> t)
-> Peek [(ContainerKey t, MapValue t)] -> Peek t
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Peek [(ContainerKey t, MapValue t)]
forall a. Store a => Peek a
peek
{-# INLINE peekOrdMapWith #-}
peekMutableSequence
    :: Store a
    => (Int -> IO r)
    -> (r -> Int -> a -> IO ())
    -> Peek r
peekMutableSequence :: forall a r.
Store a =>
(Int -> IO r) -> (r -> Int -> a -> IO ()) -> Peek r
peekMutableSequence Int -> IO r
new r -> Int -> a -> IO ()
write = do
    Int
n <- Peek Int
forall a. Store a => Peek a
peek
    r
mut <- IO r -> Peek r
forall a. IO a -> Peek a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (Int -> IO r
new Int
n)
    [Int] -> (Int -> Peek ()) -> Peek ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
t a -> (a -> m b) -> m ()
forM_ [Int
0..Int
nInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1] ((Int -> Peek ()) -> Peek ()) -> (Int -> Peek ()) -> Peek ()
forall a b. (a -> b) -> a -> b
$ \Int
i -> Peek a
forall a. Store a => Peek a
peek Peek a -> (a -> Peek ()) -> Peek ()
forall a b. Peek a -> (a -> Peek b) -> Peek b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= IO () -> Peek ()
forall a. IO a -> Peek a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> Peek ()) -> (a -> IO ()) -> a -> Peek ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. r -> Int -> a -> IO ()
write r
mut Int
i
    r -> Peek r
forall a. a -> Peek a
forall (m :: * -> *) a. Monad m => a -> m a
return r
mut
{-# INLINE peekMutableSequence #-}
{-# INLINE skip #-}
skip :: Int -> Peek ()
skip :: Int -> Peek ()
skip Int
len = (PeekState -> Ptr Word8 -> IO (PeekResult ())) -> Peek ()
forall a. (PeekState -> Ptr Word8 -> IO (PeekResult a)) -> Peek a
Peek ((PeekState -> Ptr Word8 -> IO (PeekResult ())) -> Peek ())
-> (PeekState -> Ptr Word8 -> IO (PeekResult ())) -> Peek ()
forall a b. (a -> b) -> a -> b
$ \PeekState
ps Ptr Word8
ptr -> do
    let ptr2 :: Ptr Word8
ptr2 = Ptr Word8
ptr Ptr Word8 -> Int -> Ptr Word8
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
len
        remaining :: Int
remaining = PeekState -> Ptr Word8
peekStateEndPtr PeekState
ps Ptr Word8 -> Ptr Word8 -> Int
forall a b. Ptr a -> Ptr b -> Int
`minusPtr` Ptr Word8
ptr
    Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Int
len Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
remaining) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ 
        Int -> Int -> String -> IO ()
forall void. Int -> Int -> String -> IO void
tooManyBytes Int
len Int
remaining String
"skip"
    PeekResult () -> IO (PeekResult ())
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (PeekResult () -> IO (PeekResult ()))
-> PeekResult () -> IO (PeekResult ())
forall a b. (a -> b) -> a -> b
$ Ptr Word8 -> () -> PeekResult ()
forall a. Ptr Word8 -> a -> PeekResult a
PeekResult Ptr Word8
ptr2 ()
{-# INLINE isolate #-}
isolate :: Int -> Peek a -> Peek a
isolate :: forall a. Int -> Peek a -> Peek a
isolate Int
len Peek a
m = (PeekState -> Ptr Word8 -> IO (PeekResult a)) -> Peek a
forall a. (PeekState -> Ptr Word8 -> IO (PeekResult a)) -> Peek a
Peek ((PeekState -> Ptr Word8 -> IO (PeekResult a)) -> Peek a)
-> (PeekState -> Ptr Word8 -> IO (PeekResult a)) -> Peek a
forall a b. (a -> b) -> a -> b
$ \PeekState
ps Ptr Word8
ptr -> do
    let end :: Ptr Word8
end = PeekState -> Ptr Word8
peekStateEndPtr PeekState
ps
        ptr2 :: Ptr Word8
ptr2 = Ptr Word8
ptr Ptr Word8 -> Int -> Ptr Word8
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
len
        remaining :: Int
remaining = Ptr Word8
end Ptr Word8 -> Ptr Word8 -> Int
forall a b. Ptr a -> Ptr b -> Int
`minusPtr` Ptr Word8
ptr
    Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Int
len Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
remaining) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ 
        Int -> Int -> String -> IO ()
forall void. Int -> Int -> String -> IO void
tooManyBytes Int
len Int
remaining String
"isolate"
    PeekResult Ptr Word8
ptr' a
x <- Peek a -> PeekState -> Ptr Word8 -> IO (PeekResult a)
forall a. Peek a -> PeekState -> Ptr Word8 -> IO (PeekResult a)
runPeek Peek a
m PeekState
ps Ptr Word8
ptr
    Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Ptr Word8
ptr' Ptr Word8 -> Ptr Word8 -> Bool
forall a. Ord a => a -> a -> Bool
> Ptr Word8
end) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
        PeekException -> IO ()
forall e a. Exception e => e -> IO a
throwIO (PeekException -> IO ()) -> PeekException -> IO ()
forall a b. (a -> b) -> a -> b
$ Int -> Text -> PeekException
PeekException (Ptr Word8
ptr' Ptr Word8 -> Ptr Word8 -> Int
forall a b. Ptr a -> Ptr b -> Int
`minusPtr` Ptr Word8
end) Text
"Overshot end of isolated bytes"
    PeekResult a -> IO (PeekResult a)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (PeekResult a -> IO (PeekResult a))
-> PeekResult a -> IO (PeekResult a)
forall a b. (a -> b) -> a -> b
$ Ptr Word8 -> a -> PeekResult a
forall a. Ptr Word8 -> a -> PeekResult a
PeekResult Ptr Word8
ptr2 a
x
instance Store a => Store (V.Vector a) where
    size :: Size (Vector a)
size = Size (Vector a)
forall t. (IsSequence t, Store (Element t)) => Size t
sizeSequence
    poke :: Vector a -> Poke ()
poke = Vector a -> Poke ()
forall t. (IsSequence t, Store (Element t)) => t -> Poke ()
pokeSequence
    peek :: Peek (Vector a)
peek = MVector RealWorld a -> Peek (Vector a)
MVector (PrimState Peek) a -> Peek (Vector a)
forall (m :: * -> *) a.
PrimMonad m =>
MVector (PrimState m) a -> m (Vector a)
V.unsafeFreeze (MVector RealWorld a -> Peek (Vector a))
-> Peek (MVector RealWorld a) -> Peek (Vector a)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< (Int -> IO (MVector RealWorld a))
-> (MVector RealWorld a -> Int -> a -> IO ())
-> Peek (MVector RealWorld a)
forall a r.
Store a =>
(Int -> IO r) -> (r -> Int -> a -> IO ()) -> Peek r
peekMutableSequence Int -> IO (MVector RealWorld a)
Int -> IO (MVector (PrimState IO) a)
forall (m :: * -> *) a.
PrimMonad m =>
Int -> m (MVector (PrimState m) a)
MV.new MVector RealWorld a -> Int -> a -> IO ()
MVector (PrimState IO) a -> Int -> a -> IO ()
forall (m :: * -> *) a.
PrimMonad m =>
MVector (PrimState m) a -> Int -> a -> m ()
MV.write
#if MIN_VERSION_vector(0,13,2)
instance Store a => Store (SCV.Vector a) where
    size :: Size (Vector a)
size = Size (Vector a)
forall t. (IsSequence t, Store (Element t)) => Size t
sizeSequence
    poke :: Vector a -> Poke ()
poke = Vector a -> Poke ()
forall t. (IsSequence t, Store (Element t)) => t -> Poke ()
pokeSequence
    peek :: Peek (Vector a)
peek = MVector RealWorld a -> Peek (Vector a)
MVector (PrimState Peek) a -> Peek (Vector a)
forall (m :: * -> *) a.
PrimMonad m =>
MVector (PrimState m) a -> m (Vector a)
SCV.unsafeFreeze (MVector RealWorld a -> Peek (Vector a))
-> Peek (MVector RealWorld a) -> Peek (Vector a)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< (Int -> IO (MVector RealWorld a))
-> (MVector RealWorld a -> Int -> a -> IO ())
-> Peek (MVector RealWorld a)
forall a r.
Store a =>
(Int -> IO r) -> (r -> Int -> a -> IO ()) -> Peek r
peekMutableSequence Int -> IO (MVector RealWorld a)
Int -> IO (MVector (PrimState IO) a)
forall (m :: * -> *) a.
PrimMonad m =>
Int -> m (MVector (PrimState m) a)
MSCV.new MVector RealWorld a -> Int -> a -> IO ()
MVector (PrimState IO) a -> Int -> a -> IO ()
forall (m :: * -> *) a.
PrimMonad m =>
MVector (PrimState m) a -> Int -> a -> m ()
MSCV.write
#endif
instance Storable a => Store (SV.Vector a) where
    size :: Size (Vector a)
size = (Vector a -> Int) -> Size (Vector a)
forall a. (a -> Int) -> Size a
VarSize ((Vector a -> Int) -> Size (Vector a))
-> (Vector a -> Int) -> Size (Vector a)
forall a b. (a -> b) -> a -> b
$ \Vector a
x ->
        Int -> Int
forall a. Storable a => a -> Int
sizeOf (Int
forall a. HasCallStack => a
undefined :: Int) Int -> Int -> Int
forall a. Num a => a -> a -> a
+
        a -> Int
forall a. Storable a => a -> Int
sizeOf (a
forall a. HasCallStack => a
undefined :: a) Int -> Int -> Int
forall a. Num a => a -> a -> a
* Vector a -> Int
forall a. Storable a => Vector a -> Int
SV.length Vector a
x
    poke :: Vector a -> Poke ()
poke Vector a
x = do
        let (ForeignPtr a
fptr, Int
len) = Vector a -> (ForeignPtr a, Int)
forall a. Vector a -> (ForeignPtr a, Int)
SV.unsafeToForeignPtr0 Vector a
x
        Int -> Poke ()
forall a. Store a => a -> Poke ()
poke Int
len
        ForeignPtr a -> Int -> Int -> Poke ()
forall a. ForeignPtr a -> Int -> Int -> Poke ()
pokeFromForeignPtr ForeignPtr a
fptr Int
0 (a -> Int
forall a. Storable a => a -> Int
sizeOf (a
forall a. HasCallStack => a
undefined :: a) Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
len)
    peek :: Peek (Vector a)
peek = do
        Int
len <- Peek Int
forall a. Store a => Peek a
peek
        ForeignPtr a
fp <- String -> Int -> Peek (ForeignPtr a)
forall a. String -> Int -> Peek (ForeignPtr a)
peekToPlainForeignPtr String
"Data.Storable.Vector.Vector" (a -> Int
forall a. Storable a => a -> Int
sizeOf (a
forall a. HasCallStack => a
undefined :: a) Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
len)
        IO (Vector a) -> Peek (Vector a)
forall a. IO a -> Peek a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Vector a) -> Peek (Vector a))
-> IO (Vector a) -> Peek (Vector a)
forall a b. (a -> b) -> a -> b
$ MVector (PrimState IO) a -> IO (Vector a)
forall a (m :: * -> *).
(Storable a, PrimMonad m) =>
MVector (PrimState m) a -> m (Vector a)
SV.unsafeFreeze (Int -> ForeignPtr a -> MVector RealWorld a
forall s a. Int -> ForeignPtr a -> MVector s a
MSV.MVector Int
len ForeignPtr a
fp)
instance Store BS.ByteString where
    size :: Size ByteString
size = (ByteString -> Int) -> Size ByteString
forall a. (a -> Int) -> Size a
VarSize ((ByteString -> Int) -> Size ByteString)
-> (ByteString -> Int) -> Size ByteString
forall a b. (a -> b) -> a -> b
$ \ByteString
x ->
        Int -> Int
forall a. Storable a => a -> Int
sizeOf (Int
forall a. HasCallStack => a
undefined :: Int) Int -> Int -> Int
forall a. Num a => a -> a -> a
+
        ByteString -> Int
BS.length ByteString
x
    poke :: ByteString -> Poke ()
poke ByteString
x = do
        let (ForeignPtr Word8
sourceFp, Int
sourceOffset, Int
sourceLength) = ByteString -> (ForeignPtr Word8, Int, Int)
BS.toForeignPtr ByteString
x
        Int -> Poke ()
forall a. Store a => a -> Poke ()
poke Int
sourceLength
        ForeignPtr Word8 -> Int -> Int -> Poke ()
forall a. ForeignPtr a -> Int -> Int -> Poke ()
pokeFromForeignPtr ForeignPtr Word8
sourceFp Int
sourceOffset Int
sourceLength
    peek :: Peek ByteString
peek = do
        Int
len <- Peek Int
forall a. Store a => Peek a
peek
        ForeignPtr Word8
fp <- String -> Int -> Peek (ForeignPtr Word8)
forall a. String -> Int -> Peek (ForeignPtr a)
peekToPlainForeignPtr String
"Data.ByteString.ByteString" Int
len
        ByteString -> Peek ByteString
forall a. a -> Peek a
forall (m :: * -> *) a. Monad m => a -> m a
return (ForeignPtr Word8 -> Int -> Int -> ByteString
BS.PS ForeignPtr Word8
fp Int
0 Int
len)
#if MIN_VERSION_template_haskell(2,16,0)
instance Store Bytes where
    size :: Size Bytes
size = (Bytes -> Int) -> Size Bytes
forall a. (a -> Int) -> Size a
VarSize ((Bytes -> Int) -> Size Bytes) -> (Bytes -> Int) -> Size Bytes
forall a b. (a -> b) -> a -> b
$ \Bytes
x ->
        Int -> Int
forall a. Storable a => a -> Int
sizeOf (Int
forall a. HasCallStack => a
undefined :: Int) Int -> Int -> Int
forall a. Num a => a -> a -> a
+
        Word -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Bytes -> Word
bytesSize Bytes
x)
    poke :: Bytes -> Poke ()
poke (Bytes ForeignPtr Word8
sourceFp Word
sourceOffset Word
sourceLength) = do
        Word -> Poke ()
forall a. Store a => a -> Poke ()
poke Word
sourceLength
        ForeignPtr Word8 -> Int -> Int -> Poke ()
forall a. ForeignPtr a -> Int -> Int -> Poke ()
pokeFromForeignPtr ForeignPtr Word8
sourceFp (Word -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word
sourceOffset) (Word -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word
sourceLength)
    peek :: Peek Bytes
peek = do
        Word
len <- Peek Word
forall a. Store a => Peek a
peek
        ForeignPtr Word8
fp <- String -> Int -> Peek (ForeignPtr Word8)
forall a. String -> Int -> Peek (ForeignPtr a)
peekToPlainForeignPtr String
"Data.ByteString.ByteString" (Word -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word
len)
        Bytes -> Peek Bytes
forall a. a -> Peek a
forall (m :: * -> *) a. Monad m => a -> m a
return (ForeignPtr Word8 -> Word -> Word -> Bytes
Bytes ForeignPtr Word8
fp Word
0 Word
len)
#endif
instance Store SBS.ShortByteString where
    size :: Size ShortByteString
size = (ShortByteString -> Int) -> Size ShortByteString
forall a. (a -> Int) -> Size a
VarSize ((ShortByteString -> Int) -> Size ShortByteString)
-> (ShortByteString -> Int) -> Size ShortByteString
forall a b. (a -> b) -> a -> b
$ \ShortByteString
x ->
         Int -> Int
forall a. Storable a => a -> Int
sizeOf (Int
forall a. HasCallStack => a
undefined :: Int) Int -> Int -> Int
forall a. Num a => a -> a -> a
+
         ShortByteString -> Int
SBS.length ShortByteString
x
    poke :: ShortByteString -> Poke ()
poke x :: ShortByteString
x@(SBS.SBS ByteArray#
arr) = do
        let len :: Int
len = ShortByteString -> Int
SBS.length ShortByteString
x
        Int -> Poke ()
forall a. Store a => a -> Poke ()
poke Int
len
        ByteArray# -> Int -> Int -> Poke ()
pokeFromByteArray ByteArray#
arr Int
0 Int
len
    peek :: Peek ShortByteString
peek = do
        Int
len <- Peek Int
forall a. Store a => Peek a
peek
        ByteArray ByteArray#
array <- String -> Int -> Peek ByteArray
peekToByteArray String
"Data.ByteString.Short.ShortByteString" Int
len
        ShortByteString -> Peek ShortByteString
forall a. a -> Peek a
forall (m :: * -> *) a. Monad m => a -> m a
return (ByteArray# -> ShortByteString
SBS.SBS ByteArray#
array)
instance Store LBS.ByteString where
    size :: Size ByteString
size = (ByteString -> Int) -> Size ByteString
forall a. (a -> Int) -> Size a
VarSize ((ByteString -> Int) -> Size ByteString)
-> (ByteString -> Int) -> Size ByteString
forall a b. (a -> b) -> a -> b
$ \ByteString
x ->
         Int -> Int
forall a. Storable a => a -> Int
sizeOf (Int
forall a. HasCallStack => a
undefined :: Int)  Int -> Int -> Int
forall a. Num a => a -> a -> a
+
         Int64 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (ByteString -> Int64
LBS.length ByteString
x)
    
    poke :: ByteString -> Poke ()
poke = ByteString -> Poke ()
forall a. Store a => a -> Poke ()
poke (ByteString -> Poke ())
-> (ByteString -> ByteString) -> ByteString -> Poke ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> ByteString
LBS.toStrict
    peek :: Peek ByteString
peek = (ByteString -> ByteString) -> Peek ByteString -> Peek ByteString
forall a b. (a -> b) -> Peek a -> Peek b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ByteString -> ByteString
LBS.fromStrict Peek ByteString
forall a. Store a => Peek a
peek
instance Store T.Text where
#if MIN_VERSION_text(2,0,0)
    size :: Size Text
size = (Text -> Int) -> Size Text
forall a. (a -> Int) -> Size a
VarSize ((Text -> Int) -> Size Text) -> (Text -> Int) -> Size Text
forall a b. (a -> b) -> a -> b
$ \Text
x ->
        Int -> Int
forall a. Storable a => a -> Int
sizeOf (Int
forall a. HasCallStack => a
undefined :: Int) Int -> Int -> Int
forall a. Num a => a -> a -> a
+
        Text -> Int
T.lengthWord8 Text
x
    poke :: Text -> Poke ()
poke Text
x = do
        let !(T.Text (TA.ByteArray ByteArray#
array) Int
w8Off Int
w8Len) = Text
x
        Int -> Poke ()
forall a. Store a => a -> Poke ()
poke Int
w8Len
        ByteArray# -> Int -> Int -> Poke ()
pokeFromByteArray ByteArray#
array Int
w8Off Int
w8Len
    peek :: Peek Text
peek = do
        Int
w8Len <- Peek Int
forall a. Store a => Peek a
peek
        ByteArray ByteArray#
array <- String -> Int -> Peek ByteArray
peekToByteArray String
"Data.Text.Text" Int
w8Len
        Text -> Peek Text
forall a. a -> Peek a
forall (m :: * -> *) a. Monad m => a -> m a
return (Array -> Int -> Int -> Text
T.Text (ByteArray# -> Array
TA.ByteArray ByteArray#
array) Int
0 Int
w8Len)
#else
    size = VarSize $ \x ->
        sizeOf (undefined :: Int) +
        2 * (T.lengthWord16 x)
    poke x = do
        let !(T.Text (TA.Array array) w16Off w16Len) = x
        poke w16Len
        pokeFromByteArray array (2 * w16Off) (2 * w16Len)
    peek = do
        w16Len <- peek
        ByteArray array <- peekToByteArray "Data.Text.Text" (2 * w16Len)
        return (T.Text (TA.Array array) 0 w16Len)
#endif
newtype StaticSize (n :: Nat) a = StaticSize { forall (n :: Nat) a. StaticSize n a -> a
unStaticSize :: a }
    deriving (StaticSize n a -> StaticSize n a -> Bool
(StaticSize n a -> StaticSize n a -> Bool)
-> (StaticSize n a -> StaticSize n a -> Bool)
-> Eq (StaticSize n a)
forall (n :: Nat) a.
Eq a =>
StaticSize n a -> StaticSize n a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: forall (n :: Nat) a.
Eq a =>
StaticSize n a -> StaticSize n a -> Bool
== :: StaticSize n a -> StaticSize n a -> Bool
$c/= :: forall (n :: Nat) a.
Eq a =>
StaticSize n a -> StaticSize n a -> Bool
/= :: StaticSize n a -> StaticSize n a -> Bool
Eq, Int -> StaticSize n a -> String -> String
[StaticSize n a] -> String -> String
StaticSize n a -> String
(Int -> StaticSize n a -> String -> String)
-> (StaticSize n a -> String)
-> ([StaticSize n a] -> String -> String)
-> Show (StaticSize n a)
forall (n :: Nat) a.
Show a =>
Int -> StaticSize n a -> String -> String
forall (n :: Nat) a. Show a => [StaticSize n a] -> String -> String
forall (n :: Nat) a. Show a => StaticSize n a -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: forall (n :: Nat) a.
Show a =>
Int -> StaticSize n a -> String -> String
showsPrec :: Int -> StaticSize n a -> String -> String
$cshow :: forall (n :: Nat) a. Show a => StaticSize n a -> String
show :: StaticSize n a -> String
$cshowList :: forall (n :: Nat) a. Show a => [StaticSize n a] -> String -> String
showList :: [StaticSize n a] -> String -> String
Show, Eq (StaticSize n a)
Eq (StaticSize n a) =>
(StaticSize n a -> StaticSize n a -> Ordering)
-> (StaticSize n a -> StaticSize n a -> Bool)
-> (StaticSize n a -> StaticSize n a -> Bool)
-> (StaticSize n a -> StaticSize n a -> Bool)
-> (StaticSize n a -> StaticSize n a -> Bool)
-> (StaticSize n a -> StaticSize n a -> StaticSize n a)
-> (StaticSize n a -> StaticSize n a -> StaticSize n a)
-> Ord (StaticSize n a)
StaticSize n a -> StaticSize n a -> Bool
StaticSize n a -> StaticSize n a -> Ordering
StaticSize n a -> StaticSize n a -> StaticSize n a
forall (n :: Nat) a. Ord a => Eq (StaticSize n a)
forall (n :: Nat) a.
Ord a =>
StaticSize n a -> StaticSize n a -> Bool
forall (n :: Nat) a.
Ord a =>
StaticSize n a -> StaticSize n a -> Ordering
forall (n :: Nat) a.
Ord a =>
StaticSize n a -> StaticSize n a -> StaticSize n a
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 :: forall (n :: Nat) a.
Ord a =>
StaticSize n a -> StaticSize n a -> Ordering
compare :: StaticSize n a -> StaticSize n a -> Ordering
$c< :: forall (n :: Nat) a.
Ord a =>
StaticSize n a -> StaticSize n a -> Bool
< :: StaticSize n a -> StaticSize n a -> Bool
$c<= :: forall (n :: Nat) a.
Ord a =>
StaticSize n a -> StaticSize n a -> Bool
<= :: StaticSize n a -> StaticSize n a -> Bool
$c> :: forall (n :: Nat) a.
Ord a =>
StaticSize n a -> StaticSize n a -> Bool
> :: StaticSize n a -> StaticSize n a -> Bool
$c>= :: forall (n :: Nat) a.
Ord a =>
StaticSize n a -> StaticSize n a -> Bool
>= :: StaticSize n a -> StaticSize n a -> Bool
$cmax :: forall (n :: Nat) a.
Ord a =>
StaticSize n a -> StaticSize n a -> StaticSize n a
max :: StaticSize n a -> StaticSize n a -> StaticSize n a
$cmin :: forall (n :: Nat) a.
Ord a =>
StaticSize n a -> StaticSize n a -> StaticSize n a
min :: StaticSize n a -> StaticSize n a -> StaticSize n a
Ord, Typeable (StaticSize n a)
Typeable (StaticSize n a) =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> StaticSize n a -> c (StaticSize n a))
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c (StaticSize n a))
-> (StaticSize n a -> Constr)
-> (StaticSize n a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c (StaticSize n a)))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e))
    -> Maybe (c (StaticSize n a)))
-> ((forall b. Data b => b -> b)
    -> StaticSize n a -> StaticSize n a)
-> (forall r r'.
    (r -> r' -> r)
    -> r -> (forall d. Data d => d -> r') -> StaticSize n a -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r -> (forall d. Data d => d -> r') -> StaticSize n a -> r)
-> (forall u.
    (forall d. Data d => d -> u) -> StaticSize n a -> [u])
-> (forall u.
    Int -> (forall d. Data d => d -> u) -> StaticSize n a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d)
    -> StaticSize n a -> m (StaticSize n a))
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d)
    -> StaticSize n a -> m (StaticSize n a))
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d)
    -> StaticSize n a -> m (StaticSize n a))
-> Data (StaticSize n a)
StaticSize n a -> Constr
StaticSize n a -> DataType
(forall b. Data b => b -> b) -> StaticSize n a -> StaticSize n a
forall (n :: Nat) a.
(KnownNat n, Data a) =>
Typeable (StaticSize n a)
forall (n :: Nat) a.
(KnownNat n, Data a) =>
StaticSize n a -> Constr
forall (n :: Nat) a.
(KnownNat n, Data a) =>
StaticSize n a -> DataType
forall (n :: Nat) a.
(KnownNat n, Data a) =>
(forall b. Data b => b -> b) -> StaticSize n a -> StaticSize n a
forall (n :: Nat) a u.
(KnownNat n, Data a) =>
Int -> (forall d. Data d => d -> u) -> StaticSize n a -> u
forall (n :: Nat) a u.
(KnownNat n, Data a) =>
(forall d. Data d => d -> u) -> StaticSize n a -> [u]
forall (n :: Nat) a r r'.
(KnownNat n, Data a) =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> StaticSize n a -> r
forall (n :: Nat) a r r'.
(KnownNat n, Data a) =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> StaticSize n a -> r
forall (n :: Nat) a (m :: * -> *).
(KnownNat n, Data a, Monad m) =>
(forall d. Data d => d -> m d)
-> StaticSize n a -> m (StaticSize n a)
forall (n :: Nat) a (m :: * -> *).
(KnownNat n, Data a, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> StaticSize n a -> m (StaticSize n a)
forall (n :: Nat) a (c :: * -> *).
(KnownNat n, Data a) =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (StaticSize n a)
forall (n :: Nat) a (c :: * -> *).
(KnownNat n, Data a) =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> StaticSize n a -> c (StaticSize n a)
forall (n :: Nat) a (t :: * -> *) (c :: * -> *).
(KnownNat n, Data a, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (StaticSize n a))
forall (n :: Nat) a (t :: * -> * -> *) (c :: * -> *).
(KnownNat n, Data a, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (StaticSize n a))
forall a.
Typeable a =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u.
Int -> (forall d. Data d => d -> u) -> StaticSize n a -> u
forall u. (forall d. Data d => d -> u) -> StaticSize n a -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> StaticSize n a -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> StaticSize n a -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> StaticSize n a -> m (StaticSize n a)
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> StaticSize n a -> m (StaticSize n a)
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (StaticSize n a)
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> StaticSize n a -> c (StaticSize n a)
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (StaticSize n a))
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (StaticSize n a))
$cgfoldl :: forall (n :: Nat) a (c :: * -> *).
(KnownNat n, Data a) =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> StaticSize n a -> c (StaticSize n a)
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> StaticSize n a -> c (StaticSize n a)
$cgunfold :: forall (n :: Nat) a (c :: * -> *).
(KnownNat n, Data a) =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (StaticSize n a)
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (StaticSize n a)
$ctoConstr :: forall (n :: Nat) a.
(KnownNat n, Data a) =>
StaticSize n a -> Constr
toConstr :: StaticSize n a -> Constr
$cdataTypeOf :: forall (n :: Nat) a.
(KnownNat n, Data a) =>
StaticSize n a -> DataType
dataTypeOf :: StaticSize n a -> DataType
$cdataCast1 :: forall (n :: Nat) a (t :: * -> *) (c :: * -> *).
(KnownNat n, Data a, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (StaticSize n a))
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (StaticSize n a))
$cdataCast2 :: forall (n :: Nat) a (t :: * -> * -> *) (c :: * -> *).
(KnownNat n, Data a, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (StaticSize n a))
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (StaticSize n a))
$cgmapT :: forall (n :: Nat) a.
(KnownNat n, Data a) =>
(forall b. Data b => b -> b) -> StaticSize n a -> StaticSize n a
gmapT :: (forall b. Data b => b -> b) -> StaticSize n a -> StaticSize n a
$cgmapQl :: forall (n :: Nat) a r r'.
(KnownNat n, Data a) =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> StaticSize n a -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> StaticSize n a -> r
$cgmapQr :: forall (n :: Nat) a r r'.
(KnownNat n, Data a) =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> StaticSize n a -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> StaticSize n a -> r
$cgmapQ :: forall (n :: Nat) a u.
(KnownNat n, Data a) =>
(forall d. Data d => d -> u) -> StaticSize n a -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> StaticSize n a -> [u]
$cgmapQi :: forall (n :: Nat) a u.
(KnownNat n, Data a) =>
Int -> (forall d. Data d => d -> u) -> StaticSize n a -> u
gmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> StaticSize n a -> u
$cgmapM :: forall (n :: Nat) a (m :: * -> *).
(KnownNat n, Data a, Monad m) =>
(forall d. Data d => d -> m d)
-> StaticSize n a -> m (StaticSize n a)
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> StaticSize n a -> m (StaticSize n a)
$cgmapMp :: forall (n :: Nat) a (m :: * -> *).
(KnownNat n, Data a, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> StaticSize n a -> m (StaticSize n a)
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> StaticSize n a -> m (StaticSize n a)
$cgmapMo :: forall (n :: Nat) a (m :: * -> *).
(KnownNat n, Data a, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> StaticSize n a -> m (StaticSize n a)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> StaticSize n a -> m (StaticSize n a)
Data, Typeable, (forall x. StaticSize n a -> Rep (StaticSize n a) x)
-> (forall x. Rep (StaticSize n a) x -> StaticSize n a)
-> Generic (StaticSize n a)
forall (n :: Nat) a x. Rep (StaticSize n a) x -> StaticSize n a
forall (n :: Nat) a x. StaticSize n a -> Rep (StaticSize n a) x
forall x. Rep (StaticSize n a) x -> StaticSize n a
forall x. StaticSize n a -> Rep (StaticSize n a) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall (n :: Nat) a x. StaticSize n a -> Rep (StaticSize n a) x
from :: forall x. StaticSize n a -> Rep (StaticSize n a) x
$cto :: forall (n :: Nat) a x. Rep (StaticSize n a) x -> StaticSize n a
to :: forall x. Rep (StaticSize n a) x -> StaticSize n a
Generic)
instance NFData a => NFData (StaticSize n a)
class KnownNat n => IsStaticSize n a where
    toStaticSize :: a -> Maybe (StaticSize n a)
toStaticSizeEx :: IsStaticSize n a => a -> StaticSize n a
toStaticSizeEx :: forall (n :: Nat) a. IsStaticSize n a => a -> StaticSize n a
toStaticSizeEx a
x =
    case a -> Maybe (StaticSize n a)
forall (n :: Nat) a.
IsStaticSize n a =>
a -> Maybe (StaticSize n a)
toStaticSize a
x of
        Just StaticSize n a
r -> StaticSize n a
r
        Maybe (StaticSize n a)
Nothing -> String -> StaticSize n a
forall a. HasCallStack => String -> a
error String
"Failed to assert a static size via toStaticSizeEx"
instance KnownNat n => IsStaticSize n BS.ByteString where
    toStaticSize :: ByteString -> Maybe (StaticSize n ByteString)
toStaticSize ByteString
bs
        | ByteString -> Int
BS.length ByteString
bs Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Integer -> Int
forall a. Num a => Integer -> a
fromInteger (Proxy n -> Integer
forall (n :: Nat) (proxy :: Nat -> *).
KnownNat n =>
proxy n -> Integer
natVal (Proxy n
forall {k} (t :: k). Proxy t
Proxy :: Proxy n)) = StaticSize n ByteString -> Maybe (StaticSize n ByteString)
forall a. a -> Maybe a
Just (ByteString -> StaticSize n ByteString
forall (n :: Nat) a. a -> StaticSize n a
StaticSize ByteString
bs)
        | Bool
otherwise = Maybe (StaticSize n ByteString)
forall a. Maybe a
Nothing
instance KnownNat n => Store (StaticSize n BS.ByteString) where
    size :: Size (StaticSize n ByteString)
size = Int -> Size (StaticSize n ByteString)
forall a. Int -> Size a
ConstSize (Integer -> Int
forall a. Num a => Integer -> a
fromInteger (Proxy n -> Integer
forall (n :: Nat) (proxy :: Nat -> *).
KnownNat n =>
proxy n -> Integer
natVal (Proxy n
forall {k} (t :: k). Proxy t
Proxy :: Proxy n)))
    poke :: StaticSize n ByteString -> Poke ()
poke (StaticSize ByteString
x) = do
        let (ForeignPtr Word8
sourceFp, Int
sourceOffset, Int
sourceLength) = ByteString -> (ForeignPtr Word8, Int, Int)
BS.toForeignPtr ByteString
x
        ForeignPtr Word8 -> Int -> Int -> Poke ()
forall a. ForeignPtr a -> Int -> Int -> Poke ()
pokeFromForeignPtr ForeignPtr Word8
sourceFp Int
sourceOffset Int
sourceLength
    peek :: Peek (StaticSize n ByteString)
peek = do
        let len :: Int
len = Integer -> Int
forall a. Num a => Integer -> a
fromInteger (Proxy n -> Integer
forall (n :: Nat) (proxy :: Nat -> *).
KnownNat n =>
proxy n -> Integer
natVal (Proxy n
forall {k} (t :: k). Proxy t
Proxy :: Proxy n))
        ForeignPtr Word8
fp <- String -> Int -> Peek (ForeignPtr Word8)
forall a. String -> Int -> Peek (ForeignPtr a)
peekToPlainForeignPtr (String
"StaticSize " String -> String -> String
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show Int
len String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" Data.ByteString.ByteString") Int
len
        StaticSize n ByteString -> Peek (StaticSize n ByteString)
forall a. a -> Peek a
forall (m :: * -> *) a. Monad m => a -> m a
return (ByteString -> StaticSize n ByteString
forall (n :: Nat) a. a -> StaticSize n a
StaticSize (ForeignPtr Word8 -> Int -> Int -> ByteString
BS.PS ForeignPtr Word8
fp Int
0 Int
len))
liftStaticSize :: forall n a. (KnownNat n, Lift a) => TypeQ -> StaticSize n a -> ExpQ
liftStaticSize :: forall (n :: Nat) a.
(KnownNat n, Lift a) =>
TypeQ -> StaticSize n a -> ExpQ
liftStaticSize TypeQ
tyq (StaticSize a
x) = do
    let numTy :: TypeQ
numTy = Q TyLit -> TypeQ
forall (m :: * -> *). Quote m => m TyLit -> m Type
litT (Q TyLit -> TypeQ) -> Q TyLit -> TypeQ
forall a b. (a -> b) -> a -> b
$ Integer -> Q TyLit
forall (m :: * -> *). Quote m => Integer -> m TyLit
numTyLit (Integer -> Q TyLit) -> Integer -> Q TyLit
forall a b. (a -> b) -> a -> b
$ Proxy n -> Integer
forall (n :: Nat) (proxy :: Nat -> *).
KnownNat n =>
proxy n -> Integer
natVal (Proxy n
forall {k} (t :: k). Proxy t
Proxy :: Proxy n)
    [| StaticSize $(a -> ExpQ
forall t (m :: * -> *). (Lift t, Quote m) => t -> m Exp
forall (m :: * -> *). Quote m => a -> m Exp
lift a
x) :: StaticSize $(TypeQ
numTy) $(TypeQ
tyq) |]
#if MIN_VERSION_template_haskell(2,17,0)
staticByteStringExp :: Quote m => BS.ByteString -> m Exp
#else
staticByteStringExp :: BS.ByteString -> ExpQ
#endif
staticByteStringExp :: forall (m :: * -> *). Quote m => ByteString -> m Exp
staticByteStringExp ByteString
bs =
    [| StaticSize bs :: StaticSize $(m TyLit -> m Type
forall (m :: * -> *). Quote m => m TyLit -> m Type
litT (Integer -> m TyLit
forall (m :: * -> *). Quote m => Integer -> m TyLit
numTyLit (Int -> Integer
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
len))) BS.ByteString |]
  where
    len :: Int
len = ByteString -> Int
BS.length ByteString
bs
instance Store a => Store [a] where
    size :: Size [a]
size = Size [a]
forall t. (IsSequence t, Store (Element t)) => Size t
sizeSequence
    poke :: [a] -> Poke ()
poke = [a] -> Poke ()
forall t. (IsSequence t, Store (Element t)) => t -> Poke ()
pokeSequence
    peek :: Peek [a]
peek = Peek [a]
forall t.
(IsSequence t, Store (Element t), Index t ~ Int) =>
Peek t
peekSequence
instance Store a => Store (NE.NonEmpty a)
instance Store a => Store (Seq a) where
    size :: Size (Seq a)
size = Size (Seq a)
forall t. (IsSequence t, Store (Element t)) => Size t
sizeSequence
    poke :: Seq a -> Poke ()
poke = Seq a -> Poke ()
forall t. (IsSequence t, Store (Element t)) => t -> Poke ()
pokeSequence
    peek :: Peek (Seq a)
peek = Peek (Seq a)
forall t.
(IsSequence t, Store (Element t), Index t ~ Int) =>
Peek t
peekSequence
instance (Store a, Ord a) => Store (Set a) where
    size :: Size (Set a)
size =
        (Set a -> Int) -> Size (Set a)
forall a. (a -> Int) -> Size a
VarSize ((Set a -> Int) -> Size (Set a)) -> (Set a -> Int) -> Size (Set a)
forall a b. (a -> b) -> a -> b
$ \Set a
t ->
            Int -> Int
forall a. Storable a => a -> Int
sizeOf (Int
forall a. HasCallStack => a
undefined :: Int) Int -> Int -> Int
forall a. Num a => a -> a -> a
+
            case Size a
forall a. Store a => Size a
size of
                ConstSize Int
n -> Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
* Set a -> Int
forall a. Set a -> Int
Set.size Set a
t
                VarSize a -> Int
f -> (Int -> a -> Int) -> Int -> Set a -> Int
forall a b. (a -> b -> a) -> a -> Set b -> a
Set.foldl' (\Int
acc a
a -> Int
acc Int -> Int -> Int
forall a. Num a => a -> a -> a
+ a -> Int
f a
a) Int
0 Set a
t
    poke :: Set a -> Poke ()
poke = Set a -> Poke ()
forall t. (IsSet t, Store (Element t)) => t -> Poke ()
pokeSet
    peek :: Peek (Set a)
peek = [a] -> Set a
forall a. [a] -> Set a
Set.fromDistinctAscList ([a] -> Set a) -> Peek [a] -> Peek (Set a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Peek [a]
forall a. Store a => Peek a
peek
instance Store IntSet where
    size :: Size IntSet
size = Size IntSet
forall t. (IsSet t, Store (Element t)) => Size t
sizeSet
    poke :: IntSet -> Poke ()
poke = IntSet -> Poke ()
forall t. (IsSet t, Store (Element t)) => t -> Poke ()
pokeSet
    peek :: Peek IntSet
peek = [Int] -> IntSet
IntSet.fromDistinctAscList ([Int] -> IntSet) -> Peek [Int] -> Peek IntSet
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Peek [Int]
forall a. Store a => Peek a
peek
instance Store a => Store (IntMap a) where
    size :: Size (IntMap a)
size = Size (IntMap a)
forall t.
(Store (ContainerKey t), Store (MapValue t), IsMap t) =>
Size t
sizeOrdMap
    poke :: IntMap a -> Poke ()
poke = IntMap a -> Poke ()
forall t.
(Store (ContainerKey t), Store (MapValue t), IsMap t) =>
t -> Poke ()
pokeOrdMap
    peek :: Peek (IntMap a)
peek = ([(ContainerKey (IntMap a), MapValue (IntMap a))] -> IntMap a)
-> Peek (IntMap a)
forall t.
(Store (ContainerKey t), Store (MapValue t)) =>
([(ContainerKey t, MapValue t)] -> t) -> Peek t
peekOrdMapWith [(Int, a)] -> IntMap a
[(ContainerKey (IntMap a), MapValue (IntMap a))] -> IntMap a
forall a. [(Int, a)] -> IntMap a
IntMap.fromDistinctAscList
instance (Ord k, Store k, Store a) => Store (Map k a) where
    size :: Size (Map k a)
size =
        (Map k a -> Int) -> Size (Map k a)
forall a. (a -> Int) -> Size a
VarSize ((Map k a -> Int) -> Size (Map k a))
-> (Map k a -> Int) -> Size (Map k a)
forall a b. (a -> b) -> a -> b
$ \Map k a
t ->
            Word32 -> Int
forall a. Storable a => a -> Int
sizeOf Word32
markMapPokedInAscendingOrder Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int -> Int
forall a. Storable a => a -> Int
sizeOf (Int
forall a. HasCallStack => a
undefined :: Int) Int -> Int -> Int
forall a. Num a => a -> a -> a
+
            case (Size k
forall a. Store a => Size a
size, Size a
forall a. Store a => Size a
size) of
                (ConstSize Int
nk, ConstSize Int
na) -> (Int
nk Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
na) Int -> Int -> Int
forall a. Num a => a -> a -> a
* Map k a -> Int
forall k a. Map k a -> Int
Map.size Map k a
t
                (Size k
szk, Size a
sza) ->
                    (Int -> k -> a -> Int) -> Int -> Map k a -> Int
forall a k b. (a -> k -> b -> a) -> a -> Map k b -> a
Map.foldlWithKey'
                        (\Int
acc k
k a
a -> Int
acc Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Size k -> k -> Int
forall a. Size a -> a -> Int
getSizeWith Size k
szk k
k Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Size a -> a -> Int
forall a. Size a -> a -> Int
getSizeWith Size a
sza a
a)
                        Int
0
                        Map k a
t
    poke :: Map k a -> Poke ()
poke = Map k a -> Poke ()
forall t.
(Store (ContainerKey t), Store (MapValue t), IsMap t) =>
t -> Poke ()
pokeOrdMap
    peek :: Peek (Map k a)
peek = ([(ContainerKey (Map k a), MapValue (Map k a))] -> Map k a)
-> Peek (Map k a)
forall t.
(Store (ContainerKey t), Store (MapValue t)) =>
([(ContainerKey t, MapValue t)] -> t) -> Peek t
peekOrdMapWith [(k, a)] -> Map k a
[(ContainerKey (Map k a), MapValue (Map k a))] -> Map k a
forall k a. [(k, a)] -> Map k a
Map.fromDistinctAscList
instance (Eq k, Hashable k, Store k, Store a) => Store (HashMap k a) where
    size :: Size (HashMap k a)
size = Size (HashMap k a)
forall t.
(Store (ContainerKey t), Store (MapValue t), IsMap t) =>
Size t
sizeMap
    poke :: HashMap k a -> Poke ()
poke = HashMap k a -> Poke ()
forall t.
(Store (ContainerKey t), Store (MapValue t), IsMap t) =>
t -> Poke ()
pokeMap
    peek :: Peek (HashMap k a)
peek = Peek (HashMap k a)
forall t.
(Store (ContainerKey t), Store (MapValue t), IsMap t) =>
Peek t
peekMap
instance (Eq a, Hashable a, Store a) => Store (HashSet a) where
    size :: Size (HashSet a)
size = Size (HashSet a)
forall t. (IsSet t, Store (Element t)) => Size t
sizeSet
    poke :: HashSet a -> Poke ()
poke = HashSet a -> Poke ()
forall t. (IsSet t, Store (Element t)) => t -> Poke ()
pokeSet
    peek :: Peek (HashSet a)
peek = Peek (HashSet a)
forall t. (IsSet t, Store (Element t)) => Peek t
peekSet
instance (A.Ix i, Store i, Store e) => Store (A.Array i e) where
    size :: Size (Array i e)
size = Size (Array i e)
forall i (a :: * -> * -> *) e.
(Ix i, IArray a e, Store i, Store e) =>
Size (a i e)
sizeArray
    poke :: Array i e -> Poke ()
poke = Array i e -> Poke ()
forall i (a :: * -> * -> *) e.
(Ix i, IArray a e, Store i, Store e) =>
a i e -> Poke ()
pokeArray
    peek :: Peek (Array i e)
peek = Peek (Array i e)
forall i (a :: * -> * -> *) e.
(Ix i, IArray a e, Store i, Store e) =>
Peek (a i e)
peekArray
instance (A.Ix i, A.IArray A.UArray e, Store i, Store e) => Store (A.UArray i e) where
    size :: Size (UArray i e)
size = Size (UArray i e)
forall i (a :: * -> * -> *) e.
(Ix i, IArray a e, Store i, Store e) =>
Size (a i e)
sizeArray
    poke :: UArray i e -> Poke ()
poke = UArray i e -> Poke ()
forall i (a :: * -> * -> *) e.
(Ix i, IArray a e, Store i, Store e) =>
a i e -> Poke ()
pokeArray
    peek :: Peek (UArray i e)
peek = Peek (UArray i e)
forall i (a :: * -> * -> *) e.
(Ix i, IArray a e, Store i, Store e) =>
Peek (a i e)
peekArray
sizeArray :: (A.Ix i, A.IArray a e, Store i, Store e) => Size (a i e)
sizeArray :: forall i (a :: * -> * -> *) e.
(Ix i, IArray a e, Store i, Store e) =>
Size (a i e)
sizeArray = (a i e -> Int) -> Size (a i e)
forall a. (a -> Int) -> Size a
VarSize ((a i e -> Int) -> Size (a i e)) -> (a i e -> Int) -> Size (a i e)
forall a b. (a -> b) -> a -> b
$ \a i e
arr ->
    let bounds :: (i, i)
bounds = a i e -> (i, i)
forall i. Ix i => a i e -> (i, i)
forall (a :: * -> * -> *) e i.
(IArray a e, Ix i) =>
a i e -> (i, i)
A.bounds a i e
arr
    in  (i, i) -> Int
forall a. Store a => a -> Int
getSize (i, i)
bounds Int -> Int -> Int
forall a. Num a => a -> a -> a
+
        case Size e
forall a. Store a => Size a
size of
            ConstSize Int
n ->  Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
* (i, i) -> Int
forall a. Ix a => (a, a) -> Int
A.rangeSize (i, i)
bounds
            VarSize e -> Int
f -> (Int -> e -> Int) -> Int -> [e] -> Int
forall b a. (b -> a -> b) -> b -> [a] -> b
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' (\Int
acc e
x -> Int
acc Int -> Int -> Int
forall a. Num a => a -> a -> a
+ e -> Int
f e
x) Int
0 (a i e -> [e]
forall (a :: * -> * -> *) e i. (IArray a e, Ix i) => a i e -> [e]
A.elems a i e
arr)
{-# INLINE sizeArray #-}
pokeArray :: (A.Ix i, A.IArray a e, Store i, Store e) => a i e -> Poke ()
pokeArray :: forall i (a :: * -> * -> *) e.
(Ix i, IArray a e, Store i, Store e) =>
a i e -> Poke ()
pokeArray a i e
arr = do
    (i, i) -> Poke ()
forall a. Store a => a -> Poke ()
poke (a i e -> (i, i)
forall i. Ix i => a i e -> (i, i)
forall (a :: * -> * -> *) e i.
(IArray a e, Ix i) =>
a i e -> (i, i)
A.bounds a i e
arr)
    [e] -> (e -> Poke ()) -> Poke ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
t a -> (a -> m b) -> m ()
forM_ (a i e -> [e]
forall (a :: * -> * -> *) e i. (IArray a e, Ix i) => a i e -> [e]
A.elems a i e
arr) e -> Poke ()
forall a. Store a => a -> Poke ()
poke
{-# INLINE pokeArray #-}
peekArray :: (A.Ix i, A.IArray a e, Store i, Store e) => Peek (a i e)
peekArray :: forall i (a :: * -> * -> *) e.
(Ix i, IArray a e, Store i, Store e) =>
Peek (a i e)
peekArray = do
    (i, i)
bounds <- Peek (i, i)
forall a. Store a => Peek a
peek
    let len :: Int
len = (i, i) -> Int
forall a. Ix a => (a, a) -> Int
A.rangeSize (i, i)
bounds
    [e]
elems <- Index [e] -> Peek (Element [e]) -> Peek [e]
forall seq (m :: * -> *).
(IsSequence seq, Monad m) =>
Index seq -> m (Element seq) -> m seq
forall (m :: * -> *).
Monad m =>
Index [e] -> m (Element [e]) -> m [e]
replicateM Int
Index [e]
len Peek e
Peek (Element [e])
forall a. Store a => Peek a
peek
    a i e -> Peek (a i e)
forall a. a -> Peek a
forall (m :: * -> *) a. Monad m => a -> m a
return ((i, i) -> [e] -> a i e
forall (a :: * -> * -> *) e i.
(IArray a e, Ix i) =>
(i, i) -> [e] -> a i e
A.listArray (i, i)
bounds [e]
elems)
{-# INLINE peekArray #-}
instance Store Integer where
#ifdef INTEGER_GMP
#if MIN_VERSION_integer_gmp(1,0,0)
    size :: Size Integer
size = (Integer -> Int) -> Size Integer
forall a. (a -> Int) -> Size a
VarSize ((Integer -> Int) -> Size Integer)
-> (Integer -> Int) -> Size Integer
forall a b. (a -> b) -> a -> b
$ \ Integer
x ->
        Word8 -> Int
forall a. Storable a => a -> Int
sizeOf (Word8
forall a. HasCallStack => a
undefined :: Word8) Int -> Int -> Int
forall a. Num a => a -> a -> a
+ case Integer
x of
            I.S# Int#
_ -> Int -> Int
forall a. Storable a => a -> Int
sizeOf (Int
forall a. HasCallStack => a
undefined :: Int)
            I.Jp# (I.BN# ByteArray#
arr) -> Int -> Int
forall a. Storable a => a -> Int
sizeOf (Int
forall a. HasCallStack => a
undefined :: Int) Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int# -> Int
I# (ByteArray# -> Int#
sizeofByteArray# ByteArray#
arr)
            I.Jn# (I.BN# ByteArray#
arr) -> Int -> Int
forall a. Storable a => a -> Int
sizeOf (Int
forall a. HasCallStack => a
undefined :: Int) Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int# -> Int
I# (ByteArray# -> Int#
sizeofByteArray# ByteArray#
arr)
    poke :: Integer -> Poke ()
poke (I.S# Int#
x) = Word8 -> Poke ()
forall a. Store a => a -> Poke ()
poke (Word8
0 :: Word8) Poke () -> Poke () -> Poke ()
forall a b. Poke a -> Poke b -> Poke b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Int -> Poke ()
forall a. Store a => a -> Poke ()
poke (Int# -> Int
I# Int#
x)
    poke (I.Jp# (I.BN# ByteArray#
arr)) = do
        let len :: Int
len = Int# -> Int
I# (ByteArray# -> Int#
sizeofByteArray# ByteArray#
arr)
        Word8 -> Poke ()
forall a. Store a => a -> Poke ()
poke (Word8
1 :: Word8)
        Int -> Poke ()
forall a. Store a => a -> Poke ()
poke Int
len
        ByteArray# -> Int -> Int -> Poke ()
pokeFromByteArray ByteArray#
arr Int
0 Int
len
    poke (I.Jn# (I.BN# ByteArray#
arr)) = do
        let len :: Int
len = Int# -> Int
I# (ByteArray# -> Int#
sizeofByteArray# ByteArray#
arr)
        Word8 -> Poke ()
forall a. Store a => a -> Poke ()
poke (Word8
2 :: Word8)
        Int -> Poke ()
forall a. Store a => a -> Poke ()
poke Int
len
        ByteArray# -> Int -> Int -> Poke ()
pokeFromByteArray ByteArray#
arr Int
0 Int
len
    peek :: Peek Integer
peek = do
        Word8
tag <- Peek Word8
forall a. Store a => Peek a
peek :: Peek Word8
        case Word8
tag of
            Word8
0 -> Int -> Integer
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Integer) -> Peek Int -> Peek Integer
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Peek Int
forall a. Store a => Peek a
peek :: Peek Int)
            Word8
1 -> BigNat -> Integer
I.Jp# (BigNat -> Integer) -> Peek BigNat -> Peek Integer
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Peek BigNat
peekBN
            Word8
2 -> BigNat -> Integer
I.Jn# (BigNat -> Integer) -> Peek BigNat -> Peek Integer
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Peek BigNat
peekBN
            Word8
_ -> Text -> Peek Integer
forall a. Text -> Peek a
peekException Text
"Invalid Integer tag"
      where
        peekBN :: Peek BigNat
peekBN = do
          Int
len <- Peek Int
forall a. Store a => Peek a
peek :: Peek Int
          ByteArray ByteArray#
arr <- String -> Int -> Peek ByteArray
peekToByteArray String
"GHC>Integer" Int
len
          BigNat -> Peek BigNat
forall a. a -> Peek a
forall (m :: * -> *) a. Monad m => a -> m a
return (BigNat -> Peek BigNat) -> BigNat -> Peek BigNat
forall a b. (a -> b) -> a -> b
$ ByteArray# -> BigNat
I.BN# ByteArray#
arr
#else
    
    
    size = VarSize $ \ x ->
        sizeOf (undefined :: Word8) + case x of
            I.S# _ -> sizeOf (undefined :: Int)
            I.J# sz _ -> sizeOf (undefined :: Int) + (I# sz) * sizeOf (undefined :: Word)
    poke (I.S# x) = poke (0 :: Word8) >> poke (I# x)
    poke (I.J# sz arr)
        | (I# sz) > 0 = do
            let len = I# sz * sizeOf (undefined :: Word)
            poke (1 :: Word8)
            poke len
            pokeFromByteArray arr 0 len
        | (I# sz) < 0 = do
            let len = negate (I# sz) * sizeOf (undefined :: Word)
            poke (2 :: Word8)
            poke len
            pokeFromByteArray arr 0 len
        | otherwise = do
            poke (0 :: Word8)
            poke (0 :: Int)
    peek = do
        tag <- peek :: Peek Word8
        case tag of
            0 -> fromIntegral <$> (peek :: Peek Int)
            1 -> peekJ False
            2 -> peekJ True
            _ -> peekException "Invalid Integer tag"
      where
        peekJ neg = do
          len <- peek :: Peek Int
          ByteArray arr <- peekToByteArray "GHC>Integer" len
          let (sz0, r) = len `divMod` (sizeOf (undefined :: Word))
              !(I# sz) = if neg then negate sz0 else sz0
          when (r /= 0) (peekException "Buffer size stored for encoded Integer not divisible by Word size (to get limb count).")
          return (I.J# sz arr)
#endif
#else
    
    size = VarSize $ \ x ->
        sizeOf (undefined :: Word8) + case x of
            I.Positive ds -> (1 + fromIntegral (numDigits ds)) * sizeOf (undefined :: Word)
            I.Negative ds -> (1 + fromIntegral (numDigits ds)) * sizeOf (undefined :: Word)
            I.Naught -> 0
      where
    poke x = case x of
      I.Naught -> poke (0 :: Word8)
      I.Positive ds -> do
        poke (1 :: Word8)
        poke (numDigits ds)
        pokeDigits ds
      I.Negative ds -> do
        poke (2 :: Word8)
        poke (numDigits ds)
        pokeDigits ds
      where
        pokeDigits I.None = pure ()
        pokeDigits (I.Some d ds) = poke (W# d) *> pokeDigits ds
    peek = do
      tag <- peek :: Peek Word8
      case tag of
        0 -> pure I.Naught
        1 -> do
          len <- peek :: Peek Word
          I.Positive <$> peekDigits len
        2 -> do
          len <- peek :: Peek Word
          I.Negative <$> peekDigits len
        _ -> peekException "Invalid Integer tag"
      where
        peekDigits i
          | i <= 0 = pure I.None
          | otherwise = do
              W# d <- peek
              ds <- peekDigits (i - 1)
              pure $! I.Some d ds
numDigits :: I.Digits -> Word
numDigits = go 0
  where go !acc I.None = acc
        go !acc (I.Some _ ds) = go (acc + 1) ds
#endif
instance Store Natural where
  size :: Size Nat
size = (Nat -> Integer) -> Size Integer -> Size Nat
forall a' a. (a' -> a) -> Size a -> Size a'
forall (f :: * -> *) a' a.
Contravariant f =>
(a' -> a) -> f a -> f a'
contramap Nat -> Integer
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Size Integer
forall a. Store a => Size a
size :: Size Integer)
  poke :: Nat -> Poke ()
poke = Integer -> Poke ()
forall a. Store a => a -> Poke ()
poke (Integer -> Poke ()) -> (Nat -> Integer) -> Nat -> Poke ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Nat -> Integer
forall a. Integral a => a -> Integer
toInteger
  peek :: Peek Nat
peek = do
      Integer
x <- Peek Integer
forall a. Store a => Peek a
peek :: Peek Integer
      if Integer
x Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
< Integer
0
          then Text -> Peek Nat
forall a. Text -> Peek a
peekException Text
"Encountered negative integer when expecting a Natural"
          else Nat -> Peek Nat
forall a. a -> Peek a
forall (m :: * -> *) a. Monad m => a -> m a
return (Nat -> Peek Nat) -> Nat -> Peek Nat
forall a b. (a -> b) -> a -> b
$ Integer -> Nat
forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
x
instance Store a => Store (Ratio a) where
    size :: Size (Ratio a)
size = (Ratio a -> a) -> (Ratio a -> a) -> Size (Ratio a)
forall a b c. (Store a, Store b) => (c -> a) -> (c -> b) -> Size c
combineSize (\(a
x :% a
_) -> a
x) (\(a
_ :% a
y) -> a
y)
    poke :: Ratio a -> Poke ()
poke (a
x :% a
y) = (a, a) -> Poke ()
forall a. Store a => a -> Poke ()
poke (a
x, a
y)
    peek :: Peek (Ratio a)
peek = (a -> a -> Ratio a) -> (a, a) -> Ratio a
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry a -> a -> Ratio a
forall a. a -> a -> Ratio a
(:%) ((a, a) -> Ratio a) -> Peek (a, a) -> Peek (Ratio a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Peek (a, a)
forall a. Store a => Peek a
peek
$($(derive [d| instance Deriving (Store (Fixed a)) |]))
instance Store Time.DiffTime where
    size :: Size DiffTime
size = (DiffTime -> Pico) -> Size Pico -> Size DiffTime
forall a' a. (a' -> a) -> Size a -> Size a'
forall (f :: * -> *) a' a.
Contravariant f =>
(a' -> a) -> f a -> f a'
contramap (DiffTime -> Pico
forall a b. (Real a, Fractional b) => a -> b
realToFrac :: Time.DiffTime -> Pico) Size Pico
forall a. Store a => Size a
size
    poke :: DiffTime -> Poke ()
poke = Pico -> Poke ()
forall a. Store a => a -> Poke ()
poke (Pico -> Poke ()) -> (DiffTime -> Pico) -> DiffTime -> Poke ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (DiffTime -> Pico
forall a b. (Real a, Fractional b) => a -> b
realToFrac :: Time.DiffTime -> Pico)
    peek :: Peek DiffTime
peek = (Pico -> DiffTime
forall a b. (Real a, Fractional b) => a -> b
realToFrac :: Pico -> Time.DiffTime) (Pico -> DiffTime) -> Peek Pico -> Peek DiffTime
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Peek Pico
forall a. Store a => Peek a
peek
instance Store Time.NominalDiffTime where
    size :: Size NominalDiffTime
size = (NominalDiffTime -> Pico) -> Size Pico -> Size NominalDiffTime
forall a' a. (a' -> a) -> Size a -> Size a'
forall (f :: * -> *) a' a.
Contravariant f =>
(a' -> a) -> f a -> f a'
contramap (NominalDiffTime -> Pico
forall a b. (Real a, Fractional b) => a -> b
realToFrac :: Time.NominalDiffTime -> Pico) Size Pico
forall a. Store a => Size a
size
    poke :: NominalDiffTime -> Poke ()
poke = Pico -> Poke ()
forall a. Store a => a -> Poke ()
poke (Pico -> Poke ())
-> (NominalDiffTime -> Pico) -> NominalDiffTime -> Poke ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (NominalDiffTime -> Pico
forall a b. (Real a, Fractional b) => a -> b
realToFrac :: Time.NominalDiffTime -> Pico)
    peek :: Peek NominalDiffTime
peek = (Pico -> NominalDiffTime
forall a b. (Real a, Fractional b) => a -> b
realToFrac :: Pico -> Time.NominalDiffTime) (Pico -> NominalDiffTime) -> Peek Pico -> Peek NominalDiffTime
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Peek Pico
forall a. Store a => Peek a
peek
instance Store ()
instance Store a => Store (Dual a)
instance Store a => Store (Sum a)
instance Store a => Store (Product a)
instance Store a => Store (First a)
instance Store a => Store (Last a)
instance Store a => Store (Maybe a)
instance Store a => Store (Const a b)
#if MIN_VERSION_vector(0,13,2)
deriving newtype instance Store a => Store (UV.DoNotUnboxLazy a)
deriving newtype instance Store a => Store (UV.DoNotUnboxStrict a)
deriving newtype instance Store a => Store (UV.DoNotUnboxNormalForm a)
#endif
$($(derive [d|
    instance Store a => Deriving (Store (Complex a))
    instance Store a => Deriving (Store (Identity a))
    instance Deriving (Store All)
    instance Deriving (Store Any)
    instance Deriving (Store Void)
    instance Deriving (Store Bool)
    instance (Store a, Store b) => Deriving (Store (Either a b))
    instance Deriving (Store Time.AbsoluteTime)
    instance Deriving (Store Time.Day)
    instance Deriving (Store Time.LocalTime)
    instance Deriving (Store Time.TimeOfDay)
    instance Deriving (Store Time.TimeZone)
    instance Deriving (Store Time.UTCTime)
    instance Deriving (Store Time.UniversalTime)
    instance Deriving (Store Time.ZonedTime)
    instance Deriving (Store Time.TimeLocale)
#if MIN_VERSION_time(1,8,0)
    instance Deriving (Store Time.SystemTime)
#endif
#if MIN_VERSION_time(1,9,0)
    instance Deriving (Store Time.CalendarDiffDays)
    instance Deriving (Store Time.CalendarDiffTime)
    instance Deriving (Store Time.FormatExtension)
#endif
#if MIN_VERSION_time(1,11,0)
    instance Deriving (Store Time.DayOfWeek)
    instance Deriving (Store Time.FirstWeekType)
    instance Deriving (Store Time.Quarter)
    instance Deriving (Store Time.QuarterOfYear)
#endif
    |]))
$(deriveManyStorePrimVector)
$(deriveManyStoreUnboxVector)
$(deriveManyStoreFromStorable
  
  
  
  
  
  
  
  
  (\ty ->
    case ty of
      ConT n | nameModule n == Just "Data.Text.Encoding"
            && nameBase n == "DecoderState" -> False
      ConT n | nameModule n == Just "Data.Text.Encoding"
            && nameBase n == "CodePoint" -> False
      ConT n | nameModule n == Just "Network.Socket.Types"
            && nameBase n == "In6Addr" -> False
      
      
      ConT n | n == ''AddrInfo -> False
      _ -> True
    ))
$(reifyManyWithoutInstances ''Store [''ModName, ''NameSpace, ''PkgName] (const True) >>=
   mapM (\name -> return (deriveGenericInstance [] (ConT name))))
#if !MIN_VERSION_template_haskell(2,10,0)
instance Store NameFlavour where
    size = VarSize $ \x -> getSize (0 :: Word8) + case x of
        NameS -> 0
        NameQ mn -> getSize mn
        NameU i -> getSize (I# i)
        NameL i -> getSize (I# i)
        NameG ns pn mn -> getSize ns + getSize pn + getSize mn
    poke NameS = poke (0 :: Word8)
    poke (NameQ mn) = do
        poke (1 :: Word8)
        poke mn
    poke (NameU i) = do
        poke (2 :: Word8)
        poke (I# i)
    poke (NameL i) = do
        poke (3 :: Word8)
        poke (I# i)
    poke (NameG ns pn mn) = do
        poke (4 :: Word8)
        poke ns
        poke pn
        poke mn
    peek = do
        tag <- peek
        case tag :: Word8 of
            0 -> return NameS
            1 -> NameQ <$> peek
            2 -> do
                !(I# i) <- peek
                return (NameU i)
            3 -> do
                !(I# i) <- peek
                return (NameL i)
            4 -> NameG <$> peek <*> peek <*> peek
            _ -> peekException "Invalid NameFlavour tag"
#endif
$(reifyManyWithoutInstances ''Store [''Info] (const True) >>=
   mapM deriveGenericInstanceFromName)