{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveFunctor #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MagicHash #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RankNTypes#-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# 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.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 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 Data.Void
import Data.Word
import Foreign.C.Types ()
import Foreign.Ptr (plusPtr, minusPtr)
import Foreign.Storable (Storable, sizeOf)
import GHC.Generics (Generic)
#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
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
#ifdef INTEGER_GMP
#if MIN_VERSION_integer_gmp(1,0,0)
import GHC.Prim (sizeofByteArray#)
#endif
#endif
sizeSequence :: forall t. (IsSequence t, Store (Element t)) => Size t
sizeSequence :: 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
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 :: 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
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 (m :: * -> *) a. Monad m => a -> m a
return Int
offset'')
Int
offset
t
t
(Int, ()) -> IO (Int, ())
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 :: 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
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 :: 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)
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
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 :: 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 ()
omapM_ Element t -> Poke ()
forall a. Store a => a -> Poke ()
poke t
t
{-# INLINE pokeSet #-}
peekSet :: (IsSet t, Store (Element t)) => Peek t
peekSet :: Peek t
peekSet = do
Int
len <- Peek Int
forall a. Store a => Peek a
peek
[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
replicateM Int
Index [ContainerKey t]
len Peek (Element [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 :: 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
ofoldl' (\Int
acc (k, 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 :: 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 :: 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 :: 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 (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 :: 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 :: t -> Poke ()
pokeOrdMap t
x = Word32 -> Poke ()
forall a. Store a => a -> Poke ()
poke Word32
markMapPokedInAscendingOrder Poke () -> Poke () -> Poke ()
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 :: ([(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 :: (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 (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 (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= IO () -> Peek ()
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 (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 (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 :: 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 (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)
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)
forall (m :: * -> *) a.
PrimMonad m =>
Int -> m (MVector (PrimState m) a)
MV.new MVector RealWorld a -> Int -> a -> IO ()
forall (m :: * -> *) a.
PrimMonad m =>
MVector (PrimState m) a -> Int -> a -> m ()
MV.write
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. Storable 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 (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 (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 (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 (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 (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
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
+
Int
2 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Text -> Int
T.lengthWord16 Text
x)
poke :: Text -> Poke ()
poke Text
x = do
let !(T.Text (TA.Array ByteArray#
array) Int
w16Off Int
w16Len) = Text
x
Int -> Poke ()
forall a. Store a => a -> Poke ()
poke Int
w16Len
ByteArray# -> Int -> Int -> Poke ()
pokeFromByteArray ByteArray#
array (Int
2 Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
w16Off) (Int
2 Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
w16Len)
peek :: Peek Text
peek = do
Int
w16Len <- Peek Int
forall a. Store a => Peek a
peek
ByteArray ByteArray#
array <- String -> Int -> Peek ByteArray
peekToByteArray String
"Data.Text.Text" (Int
2 Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
w16Len)
Text -> Peek Text
forall (m :: * -> *) a. Monad m => a -> m a
return (Array -> Int -> Int -> Text
T.Text (ByteArray# -> Array
TA.Array ByteArray#
array) Int
0 Int
w16Len)
newtype StaticSize (n :: Nat) a = StaticSize { 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 a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
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
$c== :: forall (n :: Nat) a.
Eq a =>
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 a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show 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
showList :: [StaticSize n a] -> String -> String
$cshowList :: forall (n :: Nat) a. Show a => [StaticSize n a] -> String -> String
show :: StaticSize n a -> String
$cshow :: forall (n :: Nat) a. Show a => StaticSize n a -> String
showsPrec :: Int -> StaticSize n a -> String -> String
$cshowsPrec :: forall (n :: Nat) a.
Show a =>
Int -> 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 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
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
min :: 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
max :: StaticSize n a -> StaticSize n a -> StaticSize n a
$cmax :: forall (n :: Nat) a.
Ord a =>
StaticSize n a -> StaticSize n a -> StaticSize n a
>= :: 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
$c< :: forall (n :: Nat) a.
Ord a =>
StaticSize n a -> StaticSize n a -> Bool
compare :: StaticSize n a -> StaticSize n a -> Ordering
$ccompare :: forall (n :: Nat) a.
Ord a =>
StaticSize n a -> StaticSize n a -> Ordering
$cp1Ord :: forall (n :: Nat) a. Ord a => Eq (StaticSize n a)
Ord, Typeable (StaticSize n a)
DataType
Constr
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 -> DataType
StaticSize n a -> Constr
(forall b. Data b => b -> b) -> StaticSize n a -> StaticSize n 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 b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> 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 (n :: Nat) a.
(KnownNat n, Data a) =>
Typeable (StaticSize n a)
forall (n :: Nat) a.
(KnownNat n, Data a) =>
StaticSize n a -> DataType
forall (n :: Nat) a.
(KnownNat n, Data a) =>
StaticSize n a -> Constr
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 (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))
$cStaticSize :: Constr
$tStaticSize :: DataType
gmapMo :: (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)
gmapMp :: (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)
gmapM :: (forall d. Data d => d -> m d)
-> StaticSize n a -> m (StaticSize n a)
$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)
gmapQi :: Int -> (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
gmapQ :: (forall d. Data d => d -> u) -> StaticSize n a -> [u]
$cgmapQ :: forall (n :: Nat) a u.
(KnownNat n, Data a) =>
(forall d. Data d => d -> u) -> StaticSize n a -> [u]
gmapQr :: (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
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> StaticSize n a -> r
$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
gmapT :: (forall b. Data b => b -> b) -> StaticSize n a -> StaticSize n a
$cgmapT :: forall (n :: Nat) a.
(KnownNat n, Data a) =>
(forall b. Data b => b -> b) -> StaticSize n a -> StaticSize n a
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> 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))
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c (StaticSize n a))
$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))
dataTypeOf :: StaticSize n a -> DataType
$cdataTypeOf :: forall (n :: Nat) a.
(KnownNat n, Data a) =>
StaticSize n a -> DataType
toConstr :: StaticSize n a -> Constr
$ctoConstr :: forall (n :: Nat) a.
(KnownNat n, Data a) =>
StaticSize n a -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> 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)
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> StaticSize n a -> 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)
$cp1Data :: forall (n :: Nat) a.
(KnownNat n, Data a) =>
Typeable (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 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
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
$cto :: forall (n :: Nat) a x. Rep (StaticSize n a) x -> StaticSize n a
$cfrom :: forall (n :: Nat) a x. StaticSize n a -> Rep (StaticSize n a) x
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 :: 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 (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 :: TypeQ -> StaticSize n a -> ExpQ
liftStaticSize TypeQ
tyq (StaticSize a
x) = do
let numTy :: TypeQ
numTy = TyLitQ -> TypeQ
litT (TyLitQ -> TypeQ) -> TyLitQ -> TypeQ
forall a b. (a -> b) -> a -> b
$ Integer -> TyLitQ
numTyLit (Integer -> TyLitQ) -> Integer -> TyLitQ
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 $(lift x) :: StaticSize $(numTy) $(tyq) |]
staticByteStringExp :: BS.ByteString -> ExpQ
staticByteStringExp :: ByteString -> ExpQ
staticByteStringExp ByteString
bs =
[| StaticSize bs :: StaticSize $(litT (numTyLit (fromIntegral 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 [(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 [(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 :: 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 (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 (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 :: 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 (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 :: 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
replicateM Int
Index [e]
len Peek (Element [e])
forall a. Store a => Peek a
peek
a i e -> Peek (a i e)
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 (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 (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 Natural
size = (Natural -> Integer) -> Size Integer -> Size Natural
forall (f :: * -> *) a b. Contravariant f => (a -> b) -> f b -> f a
contramap Natural -> Integer
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Size Integer
forall a. Store a => Size a
size :: Size Integer)
poke :: Natural -> Poke ()
poke = Integer -> Poke ()
forall a. Store a => a -> Poke ()
poke (Integer -> Poke ()) -> (Natural -> Integer) -> Natural -> Poke ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Natural -> Integer
forall a. Integral a => a -> Integer
toInteger
peek :: Peek Natural
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 Natural
forall a. Text -> Peek a
peekException Text
"Encountered negative integer when expecting a Natural"
else Natural -> Peek Natural
forall (m :: * -> *) a. Monad m => a -> m a
return (Natural -> Peek Natural) -> Natural -> Peek Natural
forall a b. (a -> b) -> a -> b
$ Integer -> Natural
forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
x
instance Store (Fixed a) where
size :: Size (Fixed a)
size = (Fixed a -> Integer) -> Size Integer -> Size (Fixed a)
forall (f :: * -> *) a b. Contravariant f => (a -> b) -> f b -> f a
contramap (\(MkFixed Integer
x) -> Integer
x) (Size Integer
forall a. Store a => Size a
size :: Size Integer)
poke :: Fixed a -> Poke ()
poke (MkFixed Integer
x) = Integer -> Poke ()
forall a. Store a => a -> Poke ()
poke Integer
x
peek :: Peek (Fixed a)
peek = Integer -> Fixed a
forall k (a :: k). Integer -> Fixed a
MkFixed (Integer -> Fixed a) -> Peek Integer -> Peek (Fixed a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Peek Integer
forall a. Store a => Peek a
peek
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
instance Store a => Store (Complex a) where
size :: Size (Complex a)
size = (Complex a -> a) -> (Complex a -> a) -> Size (Complex 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 :: Complex a -> Poke ()
poke (a
x :+ a
y) = (a, a) -> Poke ()
forall a. Store a => a -> Poke ()
poke (a
x, a
y)
peek :: Peek (Complex a)
peek = (a -> a -> Complex a) -> (a, a) -> Complex a
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry a -> a -> Complex a
forall a. a -> a -> Complex a
(:+) ((a, a) -> Complex a) -> Peek (a, a) -> Peek (Complex a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Peek (a, a)
forall a. Store a => Peek a
peek
instance Store a => Store (Identity a) where
size :: Size (Identity a)
size = (Identity a -> a) -> Size a -> Size (Identity a)
forall (f :: * -> *) a b. Contravariant f => (a -> b) -> f b -> f a
contramap (\(Identity a
x) -> a
x) Size a
forall a. Store a => Size a
size
poke :: Identity a -> Poke ()
poke (Identity a
x) = a -> Poke ()
forall a. Store a => a -> Poke ()
poke a
x
peek :: Peek (Identity a)
peek = a -> Identity a
forall a. a -> Identity a
Identity (a -> Identity a) -> Peek a -> Peek (Identity a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Peek a
forall a. Store a => Peek a
peek
instance Store Time.Day where
size :: Size Day
size = (Day -> Integer) -> Size Integer -> Size Day
forall (f :: * -> *) a b. Contravariant f => (a -> b) -> f b -> f a
contramap Day -> Integer
Time.toModifiedJulianDay (Size Integer
forall a. Store a => Size a
size :: Size Integer)
poke :: Day -> Poke ()
poke = Integer -> Poke ()
forall a. Store a => a -> Poke ()
poke (Integer -> Poke ()) -> (Day -> Integer) -> Day -> Poke ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Day -> Integer
Time.toModifiedJulianDay
peek :: Peek Day
peek = Integer -> Day
Time.ModifiedJulianDay (Integer -> Day) -> Peek Integer -> Peek Day
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Peek Integer
forall a. Store a => Peek a
peek
instance Store Time.DiffTime where
size :: Size DiffTime
size = (DiffTime -> Pico) -> Size Pico -> Size DiffTime
forall (f :: * -> *) a b. Contravariant f => (a -> b) -> f b -> 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 :: Size Pico)
poke :: DiffTime -> Poke ()
poke = (Pico -> Poke ()
forall a. Store a => a -> Poke ()
poke :: Pico -> 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
peek :: Peek DiffTime
peek = Integer -> DiffTime
Time.picosecondsToDiffTime (Integer -> DiffTime) -> Peek Integer -> Peek DiffTime
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Peek Integer
forall a. Store a => Peek a
peek
instance Store Time.UTCTime where
size :: Size UTCTime
size = (UTCTime -> Day) -> (UTCTime -> DiffTime) -> Size UTCTime
forall a b c. (Store a, Store b) => (c -> a) -> (c -> b) -> Size c
combineSize UTCTime -> Day
Time.utctDay UTCTime -> DiffTime
Time.utctDayTime
poke :: UTCTime -> Poke ()
poke (Time.UTCTime Day
day DiffTime
time) = (Day, DiffTime) -> Poke ()
forall a. Store a => a -> Poke ()
poke (Day
day, DiffTime
time)
peek :: Peek UTCTime
peek = (Day -> DiffTime -> UTCTime) -> (Day, DiffTime) -> UTCTime
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry Day -> DiffTime -> UTCTime
Time.UTCTime ((Day, DiffTime) -> UTCTime)
-> Peek (Day, DiffTime) -> Peek UTCTime
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Peek (Day, DiffTime)
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)
$($(derive [d|
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))
|]))
$(return $ map deriveTupleStoreInstance [2..7])
$(Peek (Vector Bool)
Peek (Vector Char)
Peek (Vector Double)
Peek (Vector Float)
Peek (Vector Int)
Peek (Vector Int8)
Peek (Vector Int16)
Peek (Vector Int32)
Peek (Vector Int64)
Peek (Vector Word)
Peek (Vector Word8)
Peek (Vector Word16)
Peek (Vector Word32)
Peek (Vector Word64)
Peek (Vector ())
Peek (Vector (a, b))
Peek (Vector (a, b, c))
Peek (Vector (a, b, c, d))
Peek (Vector (a, b, c, d, e))
Peek (Vector (a, b, c, d, e, f))
Peek (Vector (Complex a))
Peek (Vector (Compose f g a))
Peek (Vector (Min a))
Peek (Vector (Max a))
Peek (Vector (Arg a b))
Peek (Vector (First a))
Peek (Vector (Last a))
Peek (Vector (WrappedMonoid a))
Peek (Vector (Identity a))
Peek (Vector (Const a b))
Peek (Vector (Dual a))
Peek (Vector All)
Peek (Vector Any)
Peek (Vector (Sum a))
Peek (Vector (Product a))
Peek (Vector (Alt f a))
Peek (Vector (Down a))
Size (Vector Bool)
Size (Vector Char)
Size (Vector Double)
Size (Vector Float)
Size (Vector Int)
Size (Vector Int8)
Size (Vector Int16)
Size (Vector Int32)
Size (Vector Int64)
Size (Vector Word)
Size (Vector Word8)
Size (Vector Word16)
Size (Vector Word32)
Size (Vector Word64)
Size (Vector ())
Size (Vector (a, b))
Size (Vector (a, b, c))
Size (Vector (a, b, c, d))
Size (Vector (a, b, c, d, e))
Size (Vector (a, b, c, d, e, f))
Size (Vector (Complex a))
Size (Vector (Compose f g a))
Size (Vector (Min a))
Size (Vector (Max a))
Size (Vector (Arg a b))
Size (Vector (First a))
Size (Vector (Last a))
Size (Vector (WrappedMonoid a))
Size (Vector (Identity a))
Size (Vector (Const a b))
Size (Vector (Dual a))
Size (Vector All)
Size (Vector Any)
Size (Vector (Sum a))
Size (Vector (Product a))
Size (Vector (Alt f a))
Size (Vector (Down a))
Vector Bool -> Poke ()
Vector Char -> Poke ()
Vector Double -> Poke ()
Vector Float -> Poke ()
Vector Int -> Poke ()
Vector Int8 -> Poke ()
Vector Int16 -> Poke ()
Vector Int32 -> Poke ()
Vector Int64 -> Poke ()
Vector Word -> Poke ()
Vector Word8 -> Poke ()
Vector Word16 -> Poke ()
Vector Word32 -> Poke ()
Vector Word64 -> Poke ()
Vector () -> Poke ()
Vector (a, b) -> Poke ()
Vector (a, b, c) -> Poke ()
Vector (a, b, c, d) -> Poke ()
Vector (a, b, c, d, e) -> Poke ()
Vector (a, b, c, d, e, f) -> Poke ()
Vector (Complex a) -> Poke ()
Vector (Compose f g a) -> Poke ()
Vector (Min a) -> Poke ()
Vector (Max a) -> Poke ()
Vector (Arg a b) -> Poke ()
Vector (First a) -> Poke ()
Vector (Last a) -> Poke ()
Vector (WrappedMonoid a) -> Poke ()
Vector (Identity a) -> Poke ()
Vector (Const a b) -> Poke ()
Vector (Dual a) -> Poke ()
Vector All -> Poke ()
Vector Any -> Poke ()
Vector (Sum a) -> Poke ()
Vector (Product a) -> Poke ()
Vector (Alt f a) -> Poke ()
Vector (Down a) -> Poke ()
Size (Vector Bool)
-> (Vector Bool -> Poke ())
-> Peek (Vector Bool)
-> Store (Vector Bool)
Size (Vector Char)
-> (Vector Char -> Poke ())
-> Peek (Vector Char)
-> Store (Vector Char)
Size (Vector Double)
-> (Vector Double -> Poke ())
-> Peek (Vector Double)
-> Store (Vector Double)
Size (Vector Float)
-> (Vector Float -> Poke ())
-> Peek (Vector Float)
-> Store (Vector Float)
Size (Vector Int)
-> (Vector Int -> Poke ())
-> Peek (Vector Int)
-> Store (Vector Int)
Size (Vector Int8)
-> (Vector Int8 -> Poke ())
-> Peek (Vector Int8)
-> Store (Vector Int8)
Size (Vector Int16)
-> (Vector Int16 -> Poke ())
-> Peek (Vector Int16)
-> Store (Vector Int16)
Size (Vector Int32)
-> (Vector Int32 -> Poke ())
-> Peek (Vector Int32)
-> Store (Vector Int32)
Size (Vector Int64)
-> (Vector Int64 -> Poke ())
-> Peek (Vector Int64)
-> Store (Vector Int64)
Size (Vector Word)
-> (Vector Word -> Poke ())
-> Peek (Vector Word)
-> Store (Vector Word)
Size (Vector Word8)
-> (Vector Word8 -> Poke ())
-> Peek (Vector Word8)
-> Store (Vector Word8)
Size (Vector Word16)
-> (Vector Word16 -> Poke ())
-> Peek (Vector Word16)
-> Store (Vector Word16)
Size (Vector Word32)
-> (Vector Word32 -> Poke ())
-> Peek (Vector Word32)
-> Store (Vector Word32)
Size (Vector Word64)
-> (Vector Word64 -> Poke ())
-> Peek (Vector Word64)
-> Store (Vector Word64)
Size (Vector ())
-> (Vector () -> Poke ()) -> Peek (Vector ()) -> Store (Vector ())
Size (Vector (a, b))
-> (Vector (a, b) -> Poke ())
-> Peek (Vector (a, b))
-> Store (Vector (a, b))
Size (Vector (a, b, c))
-> (Vector (a, b, c) -> Poke ())
-> Peek (Vector (a, b, c))
-> Store (Vector (a, b, c))
Size (Vector (a, b, c, d))
-> (Vector (a, b, c, d) -> Poke ())
-> Peek (Vector (a, b, c, d))
-> Store (Vector (a, b, c, d))
Size (Vector (a, b, c, d, e))
-> (Vector (a, b, c, d, e) -> Poke ())
-> Peek (Vector (a, b, c, d, e))
-> Store (Vector (a, b, c, d, e))
Size (Vector (a, b, c, d, e, f))
-> (Vector (a, b, c, d, e, f) -> Poke ())
-> Peek (Vector (a, b, c, d, e, f))
-> Store (Vector (a, b, c, d, e, f))
Size (Vector (Complex a))
-> (Vector (Complex a) -> Poke ())
-> Peek (Vector (Complex a))
-> Store (Vector (Complex a))
Size (Vector (Compose f g a))
-> (Vector (Compose f g a) -> Poke ())
-> Peek (Vector (Compose f g a))
-> Store (Vector (Compose f g a))
Size (Vector (Min a))
-> (Vector (Min a) -> Poke ())
-> Peek (Vector (Min a))
-> Store (Vector (Min a))
Size (Vector (Max a))
-> (Vector (Max a) -> Poke ())
-> Peek (Vector (Max a))
-> Store (Vector (Max a))
Size (Vector (Arg a b))
-> (Vector (Arg a b) -> Poke ())
-> Peek (Vector (Arg a b))
-> Store (Vector (Arg a b))
Size (Vector (First a))
-> (Vector (First a) -> Poke ())
-> Peek (Vector (First a))
-> Store (Vector (First a))
Size (Vector (Last a))
-> (Vector (Last a) -> Poke ())
-> Peek (Vector (Last a))
-> Store (Vector (Last a))
Size (Vector (WrappedMonoid a))
-> (Vector (WrappedMonoid a) -> Poke ())
-> Peek (Vector (WrappedMonoid a))
-> Store (Vector (WrappedMonoid a))
Size (Vector (Identity a))
-> (Vector (Identity a) -> Poke ())
-> Peek (Vector (Identity a))
-> Store (Vector (Identity a))
Size (Vector (Const a b))
-> (Vector (Const a b) -> Poke ())
-> Peek (Vector (Const a b))
-> Store (Vector (Const a b))
Size (Vector (Dual a))
-> (Vector (Dual a) -> Poke ())
-> Peek (Vector (Dual a))
-> Store (Vector (Dual a))
Size (Vector All)
-> (Vector All -> Poke ())
-> Peek (Vector All)
-> Store (Vector All)
Size (Vector Any)
-> (Vector Any -> Poke ())
-> Peek (Vector Any)
-> Store (Vector Any)
Size (Vector (Sum a))
-> (Vector (Sum a) -> Poke ())
-> Peek (Vector (Sum a))
-> Store (Vector (Sum a))
Size (Vector (Product a))
-> (Vector (Product a) -> Poke ())
-> Peek (Vector (Product a))
-> Store (Vector (Product a))
Size (Vector (Alt f a))
-> (Vector (Alt f a) -> Poke ())
-> Peek (Vector (Alt f a))
-> Store (Vector (Alt f a))
Size (Vector (Down a))
-> (Vector (Down a) -> Poke ())
-> Peek (Vector (Down a))
-> Store (Vector (Down a))
forall a. Size a -> (a -> Poke ()) -> Peek a -> Store a
forall a. Store (Vector a) => Peek (Vector (Complex a))
forall a. Store (Vector a) => Peek (Vector (Min a))
forall a. Store (Vector a) => Peek (Vector (Max a))
forall a. Store (Vector a) => Peek (Vector (First a))
forall a. Store (Vector a) => Peek (Vector (Last a))
forall a. Store (Vector a) => Peek (Vector (WrappedMonoid a))
forall a. Store (Vector a) => Peek (Vector (Identity a))
forall a. Store (Vector a) => Peek (Vector (Dual a))
forall a. Store (Vector a) => Peek (Vector (Sum a))
forall a. Store (Vector a) => Peek (Vector (Product a))
forall a. Store (Vector a) => Peek (Vector (Down a))
forall a. Store (Vector a) => Size (Vector (Complex a))
forall a. Store (Vector a) => Size (Vector (Min a))
forall a. Store (Vector a) => Size (Vector (Max a))
forall a. Store (Vector a) => Size (Vector (First a))
forall a. Store (Vector a) => Size (Vector (Last a))
forall a. Store (Vector a) => Size (Vector (WrappedMonoid a))
forall a. Store (Vector a) => Size (Vector (Identity a))
forall a. Store (Vector a) => Size (Vector (Dual a))
forall a. Store (Vector a) => Size (Vector (Sum a))
forall a. Store (Vector a) => Size (Vector (Product a))
forall a. Store (Vector a) => Size (Vector (Down a))
forall a. Store (Vector a) => Vector (Complex a) -> Poke ()
forall a. Store (Vector a) => Vector (Min a) -> Poke ()
forall a. Store (Vector a) => Vector (Max a) -> Poke ()
forall a. Store (Vector a) => Vector (First a) -> Poke ()
forall a. Store (Vector a) => Vector (Last a) -> Poke ()
forall a. Store (Vector a) => Vector (WrappedMonoid a) -> Poke ()
forall a. Store (Vector a) => Vector (Identity a) -> Poke ()
forall a. Store (Vector a) => Vector (Dual a) -> Poke ()
forall a. Store (Vector a) => Vector (Sum a) -> Poke ()
forall a. Store (Vector a) => Vector (Product a) -> Poke ()
forall a. Store (Vector a) => Vector (Down a) -> Poke ()
forall a b. Store (Vector a) => Peek (Vector (Const a b))
forall a b. Store (Vector a) => Size (Vector (Const a b))
forall a b. Store (Vector a) => Vector (Const a b) -> Poke ()
forall a b.
(Store (Vector a), Store (Vector b)) =>
Peek (Vector (a, b))
forall a b.
(Store (Vector a), Store (Vector b)) =>
Peek (Vector (Arg a b))
forall a b.
(Store (Vector a), Store (Vector b)) =>
Size (Vector (a, b))
forall a b.
(Store (Vector a), Store (Vector b)) =>
Size (Vector (Arg a b))
forall a b.
(Store (Vector a), Store (Vector b)) =>
Vector (a, b) -> Poke ()
forall a b.
(Store (Vector a), Store (Vector b)) =>
Vector (Arg a b) -> Poke ()
forall a b c.
(Store (Vector a), Store (Vector b), Store (Vector c)) =>
Peek (Vector (a, b, c))
forall a b c.
(Store (Vector a), Store (Vector b), Store (Vector c)) =>
Size (Vector (a, b, c))
forall a b c.
(Store (Vector a), Store (Vector b), Store (Vector c)) =>
Vector (a, b, c) -> Poke ()
forall a b c d.
(Store (Vector a), Store (Vector b), Store (Vector c),
Store (Vector d)) =>
Peek (Vector (a, b, c, d))
forall a b c d.
(Store (Vector a), Store (Vector b), Store (Vector c),
Store (Vector d)) =>
Size (Vector (a, b, c, d))
forall a b c d.
(Store (Vector a), Store (Vector b), Store (Vector c),
Store (Vector d)) =>
Vector (a, b, c, d) -> Poke ()
forall a b c d e.
(Store (Vector a), Store (Vector b), Store (Vector c),
Store (Vector d), Store (Vector e)) =>
Peek (Vector (a, b, c, d, e))
forall a b c d e.
(Store (Vector a), Store (Vector b), Store (Vector c),
Store (Vector d), Store (Vector e)) =>
Size (Vector (a, b, c, d, e))
forall a b c d e.
(Store (Vector a), Store (Vector b), Store (Vector c),
Store (Vector d), Store (Vector e)) =>
Vector (a, b, c, d, e) -> Poke ()
forall a b c d e f.
(Store (Vector a), Store (Vector b), Store (Vector c),
Store (Vector d), Store (Vector e), Store (Vector f)) =>
Peek (Vector (a, b, c, d, e, f))
forall a b c d e f.
(Store (Vector a), Store (Vector b), Store (Vector c),
Store (Vector d), Store (Vector e), Store (Vector f)) =>
Size (Vector (a, b, c, d, e, f))
forall a b c d e f.
(Store (Vector a), Store (Vector b), Store (Vector c),
Store (Vector d), Store (Vector e), Store (Vector f)) =>
Vector (a, b, c, d, e, f) -> Poke ()
forall (f :: * -> *) a.
Store (Vector (f a)) =>
Peek (Vector (Alt f a))
forall (f :: * -> *) a.
Store (Vector (f a)) =>
Size (Vector (Alt f a))
forall (f :: * -> *) a.
Store (Vector (f a)) =>
Vector (Alt f a) -> Poke ()
forall (f :: * -> *) (g :: * -> *) a.
Store (Vector (f (g a))) =>
Peek (Vector (Compose f g a))
forall (f :: * -> *) (g :: * -> *) a.
Store (Vector (f (g a))) =>
Size (Vector (Compose f g a))
forall (f :: * -> *) (g :: * -> *) a.
Store (Vector (f (g a))) =>
Vector (Compose f g a) -> Poke ()
peek :: Peek (Vector (a, b, c, d, e, f))
$cpeek :: forall a b c d e f.
(Store (Vector a), Store (Vector b), Store (Vector c),
Store (Vector d), Store (Vector e), Store (Vector f)) =>
Peek (Vector (a, b, c, d, e, f))
poke :: Vector (a, b, c, d, e, f) -> Poke ()
$cpoke :: forall a b c d e f.
(Store (Vector a), Store (Vector b), Store (Vector c),
Store (Vector d), Store (Vector e), Store (Vector f)) =>
Vector (a, b, c, d, e, f) -> Poke ()
size :: Size (Vector (a, b, c, d, e, f))
$csize :: forall a b c d e f.
(Store (Vector a), Store (Vector b), Store (Vector c),
Store (Vector d), Store (Vector e), Store (Vector f)) =>
Size (Vector (a, b, c, d, e, f))
peek :: Peek (Vector (a, b, c, d, e))
$cpeek :: forall a b c d e.
(Store (Vector a), Store (Vector b), Store (Vector c),
Store (Vector d), Store (Vector e)) =>
Peek (Vector (a, b, c, d, e))
poke :: Vector (a, b, c, d, e) -> Poke ()
$cpoke :: forall a b c d e.
(Store (Vector a), Store (Vector b), Store (Vector c),
Store (Vector d), Store (Vector e)) =>
Vector (a, b, c, d, e) -> Poke ()
size :: Size (Vector (a, b, c, d, e))
$csize :: forall a b c d e.
(Store (Vector a), Store (Vector b), Store (Vector c),
Store (Vector d), Store (Vector e)) =>
Size (Vector (a, b, c, d, e))
peek :: Peek (Vector (a, b, c, d))
$cpeek :: forall a b c d.
(Store (Vector a), Store (Vector b), Store (Vector c),
Store (Vector d)) =>
Peek (Vector (a, b, c, d))
poke :: Vector (a, b, c, d) -> Poke ()
$cpoke :: forall a b c d.
(Store (Vector a), Store (Vector b), Store (Vector c),
Store (Vector d)) =>
Vector (a, b, c, d) -> Poke ()
size :: Size (Vector (a, b, c, d))
$csize :: forall a b c d.
(Store (Vector a), Store (Vector b), Store (Vector c),
Store (Vector d)) =>
Size (Vector (a, b, c, d))
peek :: Peek (Vector (Compose f g a))
$cpeek :: forall (f :: * -> *) (g :: * -> *) a.
Store (Vector (f (g a))) =>
Peek (Vector (Compose f g a))
poke :: Vector (Compose f g a) -> Poke ()
$cpoke :: forall (f :: * -> *) (g :: * -> *) a.
Store (Vector (f (g a))) =>
Vector (Compose f g a) -> Poke ()
size :: Size (Vector (Compose f g a))
$csize :: forall (f :: * -> *) (g :: * -> *) a.
Store (Vector (f (g a))) =>
Size (Vector (Compose f g a))
peek :: Peek (Vector (a, b, c))
$cpeek :: forall a b c.
(Store (Vector a), Store (Vector b), Store (Vector c)) =>
Peek (Vector (a, b, c))
poke :: Vector (a, b, c) -> Poke ()
$cpoke :: forall a b c.
(Store (Vector a), Store (Vector b), Store (Vector c)) =>
Vector (a, b, c) -> Poke ()
size :: Size (Vector (a, b, c))
$csize :: forall a b c.
(Store (Vector a), Store (Vector b), Store (Vector c)) =>
Size (Vector (a, b, c))
peek :: Peek (Vector (Const a b))
$cpeek :: forall a b. Store (Vector a) => Peek (Vector (Const a b))
poke :: Vector (Const a b) -> Poke ()
$cpoke :: forall a b. Store (Vector a) => Vector (Const a b) -> Poke ()
size :: Size (Vector (Const a b))
$csize :: forall a b. Store (Vector a) => Size (Vector (Const a b))
peek :: Peek (Vector (Arg a b))
$cpeek :: forall a b.
(Store (Vector a), Store (Vector b)) =>
Peek (Vector (Arg a b))
poke :: Vector (Arg a b) -> Poke ()
$cpoke :: forall a b.
(Store (Vector a), Store (Vector b)) =>
Vector (Arg a b) -> Poke ()
size :: Size (Vector (Arg a b))
$csize :: forall a b.
(Store (Vector a), Store (Vector b)) =>
Size (Vector (Arg a b))
peek :: Peek (Vector (Alt f a))
$cpeek :: forall (f :: * -> *) a.
Store (Vector (f a)) =>
Peek (Vector (Alt f a))
poke :: Vector (Alt f a) -> Poke ()
$cpoke :: forall (f :: * -> *) a.
Store (Vector (f a)) =>
Vector (Alt f a) -> Poke ()
size :: Size (Vector (Alt f a))
$csize :: forall (f :: * -> *) a.
Store (Vector (f a)) =>
Size (Vector (Alt f a))
peek :: Peek (Vector (a, b))
$cpeek :: forall a b.
(Store (Vector a), Store (Vector b)) =>
Peek (Vector (a, b))
poke :: Vector (a, b) -> Poke ()
$cpoke :: forall a b.
(Store (Vector a), Store (Vector b)) =>
Vector (a, b) -> Poke ()
size :: Size (Vector (a, b))
$csize :: forall a b.
(Store (Vector a), Store (Vector b)) =>
Size (Vector (a, b))
peek :: Peek (Vector (Complex a))
$cpeek :: forall a. Store (Vector a) => Peek (Vector (Complex a))
poke :: Vector (Complex a) -> Poke ()
$cpoke :: forall a. Store (Vector a) => Vector (Complex a) -> Poke ()
size :: Size (Vector (Complex a))
$csize :: forall a. Store (Vector a) => Size (Vector (Complex a))
peek :: Peek (Vector (Identity a))
$cpeek :: forall a. Store (Vector a) => Peek (Vector (Identity a))
poke :: Vector (Identity a) -> Poke ()
$cpoke :: forall a. Store (Vector a) => Vector (Identity a) -> Poke ()
size :: Size (Vector (Identity a))
$csize :: forall a. Store (Vector a) => Size (Vector (Identity a))
peek :: Peek (Vector (Down a))
$cpeek :: forall a. Store (Vector a) => Peek (Vector (Down a))
poke :: Vector (Down a) -> Poke ()
$cpoke :: forall a. Store (Vector a) => Vector (Down a) -> Poke ()
size :: Size (Vector (Down a))
$csize :: forall a. Store (Vector a) => Size (Vector (Down a))
peek :: Peek (Vector (First a))
$cpeek :: forall a. Store (Vector a) => Peek (Vector (First a))
poke :: Vector (First a) -> Poke ()
$cpoke :: forall a. Store (Vector a) => Vector (First a) -> Poke ()
size :: Size (Vector (First a))
$csize :: forall a. Store (Vector a) => Size (Vector (First a))
peek :: Peek (Vector (Last a))
$cpeek :: forall a. Store (Vector a) => Peek (Vector (Last a))
poke :: Vector (Last a) -> Poke ()
$cpoke :: forall a. Store (Vector a) => Vector (Last a) -> Poke ()
size :: Size (Vector (Last a))
$csize :: forall a. Store (Vector a) => Size (Vector (Last a))
peek :: Peek (Vector (Max a))
$cpeek :: forall a. Store (Vector a) => Peek (Vector (Max a))
poke :: Vector (Max a) -> Poke ()
$cpoke :: forall a. Store (Vector a) => Vector (Max a) -> Poke ()
size :: Size (Vector (Max a))
$csize :: forall a. Store (Vector a) => Size (Vector (Max a))
peek :: Peek (Vector (Min a))
$cpeek :: forall a. Store (Vector a) => Peek (Vector (Min a))
poke :: Vector (Min a) -> Poke ()
$cpoke :: forall a. Store (Vector a) => Vector (Min a) -> Poke ()
size :: Size (Vector (Min a))
$csize :: forall a. Store (Vector a) => Size (Vector (Min a))
peek :: Peek (Vector (WrappedMonoid a))
$cpeek :: forall a. Store (Vector a) => Peek (Vector (WrappedMonoid a))
poke :: Vector (WrappedMonoid a) -> Poke ()
$cpoke :: forall a. Store (Vector a) => Vector (WrappedMonoid a) -> Poke ()
size :: Size (Vector (WrappedMonoid a))
$csize :: forall a. Store (Vector a) => Size (Vector (WrappedMonoid a))
peek :: Peek (Vector (Dual a))
$cpeek :: forall a. Store (Vector a) => Peek (Vector (Dual a))
poke :: Vector (Dual a) -> Poke ()
$cpoke :: forall a. Store (Vector a) => Vector (Dual a) -> Poke ()
size :: Size (Vector (Dual a))
$csize :: forall a. Store (Vector a) => Size (Vector (Dual a))
peek :: Peek (Vector (Product a))
$cpeek :: forall a. Store (Vector a) => Peek (Vector (Product a))
poke :: Vector (Product a) -> Poke ()
$cpoke :: forall a. Store (Vector a) => Vector (Product a) -> Poke ()
size :: Size (Vector (Product a))
$csize :: forall a. Store (Vector a) => Size (Vector (Product a))
peek :: Peek (Vector (Sum a))
$cpeek :: forall a. Store (Vector a) => Peek (Vector (Sum a))
poke :: Vector (Sum a) -> Poke ()
$cpoke :: forall a. Store (Vector a) => Vector (Sum a) -> Poke ()
size :: Size (Vector (Sum a))
$csize :: forall a. Store (Vector a) => Size (Vector (Sum a))
peek :: Peek (Vector All)
$cpeek :: Peek (Vector All)
poke :: Vector All -> Poke ()
$cpoke :: Vector All -> Poke ()
size :: Size (Vector All)
$csize :: Size (Vector All)
peek :: Peek (Vector Any)
$cpeek :: Peek (Vector Any)
poke :: Vector Any -> Poke ()
$cpoke :: Vector Any -> Poke ()
size :: Size (Vector Any)
$csize :: Size (Vector Any)
peek :: Peek (Vector Int16)
$cpeek :: Peek (Vector Int16)
poke :: Vector Int16 -> Poke ()
$cpoke :: Vector Int16 -> Poke ()
size :: Size (Vector Int16)
$csize :: Size (Vector Int16)
peek :: Peek (Vector Int32)
$cpeek :: Peek (Vector Int32)
poke :: Vector Int32 -> Poke ()
$cpoke :: Vector Int32 -> Poke ()
size :: Size (Vector Int32)
$csize :: Size (Vector Int32)
peek :: Peek (Vector Int64)
$cpeek :: Peek (Vector Int64)
poke :: Vector Int64 -> Poke ()
$cpoke :: Vector Int64 -> Poke ()
size :: Size (Vector Int64)
$csize :: Size (Vector Int64)
peek :: Peek (Vector Int8)
$cpeek :: Peek (Vector Int8)
poke :: Vector Int8 -> Poke ()
$cpoke :: Vector Int8 -> Poke ()
size :: Size (Vector Int8)
$csize :: Size (Vector Int8)
peek :: Peek (Vector Word16)
$cpeek :: Peek (Vector Word16)
poke :: Vector Word16 -> Poke ()
$cpoke :: Vector Word16 -> Poke ()
size :: Size (Vector Word16)
$csize :: Size (Vector Word16)
peek :: Peek (Vector Word32)
$cpeek :: Peek (Vector Word32)
poke :: Vector Word32 -> Poke ()
$cpoke :: Vector Word32 -> Poke ()
size :: Size (Vector Word32)
$csize :: Size (Vector Word32)
peek :: Peek (Vector Word64)
$cpeek :: Peek (Vector Word64)
poke :: Vector Word64 -> Poke ()
$cpoke :: Vector Word64 -> Poke ()
size :: Size (Vector Word64)
$csize :: Size (Vector Word64)
peek :: Peek (Vector Word8)
$cpeek :: Peek (Vector Word8)
poke :: Vector Word8 -> Poke ()
$cpoke :: Vector Word8 -> Poke ()
size :: Size (Vector Word8)
$csize :: Size (Vector Word8)
peek :: Peek (Vector Bool)
$cpeek :: Peek (Vector Bool)
poke :: Vector Bool -> Poke ()
$cpoke :: Vector Bool -> Poke ()
size :: Size (Vector Bool)
$csize :: Size (Vector Bool)
peek :: Peek (Vector Char)
$cpeek :: Peek (Vector Char)
poke :: Vector Char -> Poke ()
$cpoke :: Vector Char -> Poke ()
size :: Size (Vector Char)
$csize :: Size (Vector Char)
peek :: Peek (Vector Double)
$cpeek :: Peek (Vector Double)
poke :: Vector Double -> Poke ()
$cpoke :: Vector Double -> Poke ()
size :: Size (Vector Double)
$csize :: Size (Vector Double)
peek :: Peek (Vector Float)
$cpeek :: Peek (Vector Float)
poke :: Vector Float -> Poke ()
$cpoke :: Vector Float -> Poke ()
size :: Size (Vector Float)
$csize :: Size (Vector Float)
peek :: Peek (Vector Int)
$cpeek :: Peek (Vector Int)
poke :: Vector Int -> Poke ()
$cpoke :: Vector Int -> Poke ()
size :: Size (Vector Int)
$csize :: Size (Vector Int)
peek :: Peek (Vector Word)
$cpeek :: Peek (Vector Word)
poke :: Vector Word -> Poke ()
$cpoke :: Vector Word -> Poke ()
size :: Size (Vector Word)
$csize :: Size (Vector Word)
peek :: Peek (Vector ())
$cpeek :: Peek (Vector ())
poke :: Vector () -> Poke ()
$cpoke :: Vector () -> Poke ()
size :: Size (Vector ())
$csize :: Size (Vector ())
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
))
$(Peek (Vector Char)
Peek (Vector Double)
Peek (Vector Float)
Peek (Vector Int)
Peek (Vector Int8)
Peek (Vector Int16)
Peek (Vector Int32)
Peek (Vector Int64)
Peek (Vector (StablePtr a))
Peek (Vector Word)
Peek (Vector Word8)
Peek (Vector Word16)
Peek (Vector Word32)
Peek (Vector Word64)
Peek (Vector (Ptr a))
Peek (Vector (FunPtr a))
Peek (Vector (Min a))
Peek (Vector (Max a))
Peek (Vector (First a))
Peek (Vector (Last a))
Peek (Vector (Identity a))
Peek (Vector CDev)
Peek (Vector CIno)
Peek (Vector CMode)
Peek (Vector COff)
Peek (Vector CPid)
Peek (Vector CSsize)
Peek (Vector CGid)
Peek (Vector CNlink)
Peek (Vector CUid)
Peek (Vector CCc)
Peek (Vector CSpeed)
Peek (Vector CTcflag)
Peek (Vector CRLim)
Peek (Vector CBlkSize)
Peek (Vector CBlkCnt)
Peek (Vector CClockId)
Peek (Vector CFsBlkCnt)
Peek (Vector CFsFilCnt)
Peek (Vector CId)
Peek (Vector CKey)
Peek (Vector CTimer)
Peek (Vector Fd)
Peek (Vector (Const a b))
Peek (Vector (Dual a))
Peek (Vector (Sum a))
Peek (Vector (Product a))
Peek (Vector (Down a))
Peek (Vector CChar)
Peek (Vector CSChar)
Peek (Vector CUChar)
Peek (Vector CShort)
Peek (Vector CUShort)
Peek (Vector CInt)
Peek (Vector CUInt)
Peek (Vector CLong)
Peek (Vector CULong)
Peek (Vector CLLong)
Peek (Vector CULLong)
Peek (Vector CBool)
Peek (Vector CFloat)
Peek (Vector CDouble)
Peek (Vector CPtrdiff)
Peek (Vector CSize)
Peek (Vector CWchar)
Peek (Vector CSigAtomic)
Peek (Vector CClock)
Peek (Vector CTime)
Peek (Vector CUSeconds)
Peek (Vector CSUSeconds)
Peek (Vector CIntPtr)
Peek (Vector CUIntPtr)
Peek (Vector CIntMax)
Peek (Vector CUIntMax)
Peek (Vector WordPtr)
Peek (Vector IntPtr)
Size (Vector Char)
Size (Vector Double)
Size (Vector Float)
Size (Vector Int)
Size (Vector Int8)
Size (Vector Int16)
Size (Vector Int32)
Size (Vector Int64)
Size (Vector (StablePtr a))
Size (Vector Word)
Size (Vector Word8)
Size (Vector Word16)
Size (Vector Word32)
Size (Vector Word64)
Size (Vector (Ptr a))
Size (Vector (FunPtr a))
Size (Vector (Min a))
Size (Vector (Max a))
Size (Vector (First a))
Size (Vector (Last a))
Size (Vector (Identity a))
Size (Vector CDev)
Size (Vector CIno)
Size (Vector CMode)
Size (Vector COff)
Size (Vector CPid)
Size (Vector CSsize)
Size (Vector CGid)
Size (Vector CNlink)
Size (Vector CUid)
Size (Vector CCc)
Size (Vector CSpeed)
Size (Vector CTcflag)
Size (Vector CRLim)
Size (Vector CBlkSize)
Size (Vector CBlkCnt)
Size (Vector CClockId)
Size (Vector CFsBlkCnt)
Size (Vector CFsFilCnt)
Size (Vector CId)
Size (Vector CKey)
Size (Vector CTimer)
Size (Vector Fd)
Size (Vector (Const a b))
Size (Vector (Dual a))
Size (Vector (Sum a))
Size (Vector (Product a))
Size (Vector (Down a))
Size (Vector CChar)
Size (Vector CSChar)
Size (Vector CUChar)
Size (Vector CShort)
Size (Vector CUShort)
Size (Vector CInt)
Size (Vector CUInt)
Size (Vector CLong)
Size (Vector CULong)
Size (Vector CLLong)
Size (Vector CULLong)
Size (Vector CBool)
Size (Vector CFloat)
Size (Vector CDouble)
Size (Vector CPtrdiff)
Size (Vector CSize)
Size (Vector CWchar)
Size (Vector CSigAtomic)
Size (Vector CClock)
Size (Vector CTime)
Size (Vector CUSeconds)
Size (Vector CSUSeconds)
Size (Vector CIntPtr)
Size (Vector CUIntPtr)
Size (Vector CIntMax)
Size (Vector CUIntMax)
Size (Vector WordPtr)
Size (Vector IntPtr)
Vector Char -> Poke ()
Vector Double -> Poke ()
Vector Float -> Poke ()
Vector Int -> Poke ()
Vector Int8 -> Poke ()
Vector Int16 -> Poke ()
Vector Int32 -> Poke ()
Vector Int64 -> Poke ()
Vector (StablePtr a) -> Poke ()
Vector Word -> Poke ()
Vector Word8 -> Poke ()
Vector Word16 -> Poke ()
Vector Word32 -> Poke ()
Vector Word64 -> Poke ()
Vector (Ptr a) -> Poke ()
Vector (FunPtr a) -> Poke ()
Vector (Min a) -> Poke ()
Vector (Max a) -> Poke ()
Vector (First a) -> Poke ()
Vector (Last a) -> Poke ()
Vector (Identity a) -> Poke ()
Vector CDev -> Poke ()
Vector CIno -> Poke ()
Vector CMode -> Poke ()
Vector COff -> Poke ()
Vector CPid -> Poke ()
Vector CSsize -> Poke ()
Vector CGid -> Poke ()
Vector CNlink -> Poke ()
Vector CUid -> Poke ()
Vector CCc -> Poke ()
Vector CSpeed -> Poke ()
Vector CTcflag -> Poke ()
Vector CRLim -> Poke ()
Vector CBlkSize -> Poke ()
Vector CBlkCnt -> Poke ()
Vector CClockId -> Poke ()
Vector CFsBlkCnt -> Poke ()
Vector CFsFilCnt -> Poke ()
Vector CId -> Poke ()
Vector CKey -> Poke ()
Vector CTimer -> Poke ()
Vector Fd -> Poke ()
Vector (Const a b) -> Poke ()
Vector (Dual a) -> Poke ()
Vector (Sum a) -> Poke ()
Vector (Product a) -> Poke ()
Vector (Down a) -> Poke ()
Vector CChar -> Poke ()
Vector CSChar -> Poke ()
Vector CUChar -> Poke ()
Vector CShort -> Poke ()
Vector CUShort -> Poke ()
Vector CInt -> Poke ()
Vector CUInt -> Poke ()
Vector CLong -> Poke ()
Vector CULong -> Poke ()
Vector CLLong -> Poke ()
Vector CULLong -> Poke ()
Vector CBool -> Poke ()
Vector CFloat -> Poke ()
Vector CDouble -> Poke ()
Vector CPtrdiff -> Poke ()
Vector CSize -> Poke ()
Vector CWchar -> Poke ()
Vector CSigAtomic -> Poke ()
Vector CClock -> Poke ()
Vector CTime -> Poke ()
Vector CUSeconds -> Poke ()
Vector CSUSeconds -> Poke ()
Vector CIntPtr -> Poke ()
Vector CUIntPtr -> Poke ()
Vector CIntMax -> Poke ()
Vector CUIntMax -> Poke ()
Vector WordPtr -> Poke ()
Vector IntPtr -> Poke ()
Size (Vector Char)
-> (Vector Char -> Poke ())
-> Peek (Vector Char)
-> Store (Vector Char)
Size (Vector Double)
-> (Vector Double -> Poke ())
-> Peek (Vector Double)
-> Store (Vector Double)
Size (Vector Float)
-> (Vector Float -> Poke ())
-> Peek (Vector Float)
-> Store (Vector Float)
Size (Vector Int)
-> (Vector Int -> Poke ())
-> Peek (Vector Int)
-> Store (Vector Int)
Size (Vector Int8)
-> (Vector Int8 -> Poke ())
-> Peek (Vector Int8)
-> Store (Vector Int8)
Size (Vector Int16)
-> (Vector Int16 -> Poke ())
-> Peek (Vector Int16)
-> Store (Vector Int16)
Size (Vector Int32)
-> (Vector Int32 -> Poke ())
-> Peek (Vector Int32)
-> Store (Vector Int32)
Size (Vector Int64)
-> (Vector Int64 -> Poke ())
-> Peek (Vector Int64)
-> Store (Vector Int64)
Size (Vector (StablePtr a))
-> (Vector (StablePtr a) -> Poke ())
-> Peek (Vector (StablePtr a))
-> Store (Vector (StablePtr a))
Size (Vector Word)
-> (Vector Word -> Poke ())
-> Peek (Vector Word)
-> Store (Vector Word)
Size (Vector Word8)
-> (Vector Word8 -> Poke ())
-> Peek (Vector Word8)
-> Store (Vector Word8)
Size (Vector Word16)
-> (Vector Word16 -> Poke ())
-> Peek (Vector Word16)
-> Store (Vector Word16)
Size (Vector Word32)
-> (Vector Word32 -> Poke ())
-> Peek (Vector Word32)
-> Store (Vector Word32)
Size (Vector Word64)
-> (Vector Word64 -> Poke ())
-> Peek (Vector Word64)
-> Store (Vector Word64)
Size (Vector (Ptr a))
-> (Vector (Ptr a) -> Poke ())
-> Peek (Vector (Ptr a))
-> Store (Vector (Ptr a))
Size (Vector (FunPtr a))
-> (Vector (FunPtr a) -> Poke ())
-> Peek (Vector (FunPtr a))
-> Store (Vector (FunPtr a))
Size (Vector (Min a))
-> (Vector (Min a) -> Poke ())
-> Peek (Vector (Min a))
-> Store (Vector (Min a))
Size (Vector (Max a))
-> (Vector (Max a) -> Poke ())
-> Peek (Vector (Max a))
-> Store (Vector (Max a))
Size (Vector (First a))
-> (Vector (First a) -> Poke ())
-> Peek (Vector (First a))
-> Store (Vector (First a))
Size (Vector (Last a))
-> (Vector (Last a) -> Poke ())
-> Peek (Vector (Last a))
-> Store (Vector (Last a))
Size (Vector (Identity a))
-> (Vector (Identity a) -> Poke ())
-> Peek (Vector (Identity a))
-> Store (Vector (Identity a))
Size (Vector CDev)
-> (Vector CDev -> Poke ())
-> Peek (Vector CDev)
-> Store (Vector CDev)
Size (Vector CIno)
-> (Vector CIno -> Poke ())
-> Peek (Vector CIno)
-> Store (Vector CIno)
Size (Vector CMode)
-> (Vector CMode -> Poke ())
-> Peek (Vector CMode)
-> Store (Vector CMode)
Size (Vector COff)
-> (Vector COff -> Poke ())
-> Peek (Vector COff)
-> Store (Vector COff)
Size (Vector CPid)
-> (Vector CPid -> Poke ())
-> Peek (Vector CPid)
-> Store (Vector CPid)
Size (Vector CSsize)
-> (Vector CSsize -> Poke ())
-> Peek (Vector CSsize)
-> Store (Vector CSsize)
Size (Vector CGid)
-> (Vector CGid -> Poke ())
-> Peek (Vector CGid)
-> Store (Vector CGid)
Size (Vector CNlink)
-> (Vector CNlink -> Poke ())
-> Peek (Vector CNlink)
-> Store (Vector CNlink)
Size (Vector CUid)
-> (Vector CUid -> Poke ())
-> Peek (Vector CUid)
-> Store (Vector CUid)
Size (Vector CCc)
-> (Vector CCc -> Poke ())
-> Peek (Vector CCc)
-> Store (Vector CCc)
Size (Vector CSpeed)
-> (Vector CSpeed -> Poke ())
-> Peek (Vector CSpeed)
-> Store (Vector CSpeed)
Size (Vector CTcflag)
-> (Vector CTcflag -> Poke ())
-> Peek (Vector CTcflag)
-> Store (Vector CTcflag)
Size (Vector CRLim)
-> (Vector CRLim -> Poke ())
-> Peek (Vector CRLim)
-> Store (Vector CRLim)
Size (Vector CBlkSize)
-> (Vector CBlkSize -> Poke ())
-> Peek (Vector CBlkSize)
-> Store (Vector CBlkSize)
Size (Vector CBlkCnt)
-> (Vector CBlkCnt -> Poke ())
-> Peek (Vector CBlkCnt)
-> Store (Vector CBlkCnt)
Size (Vector CClockId)
-> (Vector CClockId -> Poke ())
-> Peek (Vector CClockId)
-> Store (Vector CClockId)
Size (Vector CFsBlkCnt)
-> (Vector CFsBlkCnt -> Poke ())
-> Peek (Vector CFsBlkCnt)
-> Store (Vector CFsBlkCnt)
Size (Vector CFsFilCnt)
-> (Vector CFsFilCnt -> Poke ())
-> Peek (Vector CFsFilCnt)
-> Store (Vector CFsFilCnt)
Size (Vector CId)
-> (Vector CId -> Poke ())
-> Peek (Vector CId)
-> Store (Vector CId)
Size (Vector CKey)
-> (Vector CKey -> Poke ())
-> Peek (Vector CKey)
-> Store (Vector CKey)
Size (Vector CTimer)
-> (Vector CTimer -> Poke ())
-> Peek (Vector CTimer)
-> Store (Vector CTimer)
Size (Vector Fd)
-> (Vector Fd -> Poke ()) -> Peek (Vector Fd) -> Store (Vector Fd)
Size (Vector (Const a b))
-> (Vector (Const a b) -> Poke ())
-> Peek (Vector (Const a b))
-> Store (Vector (Const a b))
Size (Vector (Dual a))
-> (Vector (Dual a) -> Poke ())
-> Peek (Vector (Dual a))
-> Store (Vector (Dual a))
Size (Vector (Sum a))
-> (Vector (Sum a) -> Poke ())
-> Peek (Vector (Sum a))
-> Store (Vector (Sum a))
Size (Vector (Product a))
-> (Vector (Product a) -> Poke ())
-> Peek (Vector (Product a))
-> Store (Vector (Product a))
Size (Vector (Down a))
-> (Vector (Down a) -> Poke ())
-> Peek (Vector (Down a))
-> Store (Vector (Down a))
Size (Vector CChar)
-> (Vector CChar -> Poke ())
-> Peek (Vector CChar)
-> Store (Vector CChar)
Size (Vector CSChar)
-> (Vector CSChar -> Poke ())
-> Peek (Vector CSChar)
-> Store (Vector CSChar)
Size (Vector CUChar)
-> (Vector CUChar -> Poke ())
-> Peek (Vector CUChar)
-> Store (Vector CUChar)
Size (Vector CShort)
-> (Vector CShort -> Poke ())
-> Peek (Vector CShort)
-> Store (Vector CShort)
Size (Vector CUShort)
-> (Vector CUShort -> Poke ())
-> Peek (Vector CUShort)
-> Store (Vector CUShort)
Size (Vector CInt)
-> (Vector CInt -> Poke ())
-> Peek (Vector CInt)
-> Store (Vector CInt)
Size (Vector CUInt)
-> (Vector CUInt -> Poke ())
-> Peek (Vector CUInt)
-> Store (Vector CUInt)
Size (Vector CLong)
-> (Vector CLong -> Poke ())
-> Peek (Vector CLong)
-> Store (Vector CLong)
Size (Vector CULong)
-> (Vector CULong -> Poke ())
-> Peek (Vector CULong)
-> Store (Vector CULong)
Size (Vector CLLong)
-> (Vector CLLong -> Poke ())
-> Peek (Vector CLLong)
-> Store (Vector CLLong)
Size (Vector CULLong)
-> (Vector CULLong -> Poke ())
-> Peek (Vector CULLong)
-> Store (Vector CULLong)
Size (Vector CBool)
-> (Vector CBool -> Poke ())
-> Peek (Vector CBool)
-> Store (Vector CBool)
Size (Vector CFloat)
-> (Vector CFloat -> Poke ())
-> Peek (Vector CFloat)
-> Store (Vector CFloat)
Size (Vector CDouble)
-> (Vector CDouble -> Poke ())
-> Peek (Vector CDouble)
-> Store (Vector CDouble)
Size (Vector CPtrdiff)
-> (Vector CPtrdiff -> Poke ())
-> Peek (Vector CPtrdiff)
-> Store (Vector CPtrdiff)
Size (Vector CSize)
-> (Vector CSize -> Poke ())
-> Peek (Vector CSize)
-> Store (Vector CSize)
Size (Vector CWchar)
-> (Vector CWchar -> Poke ())
-> Peek (Vector CWchar)
-> Store (Vector CWchar)
Size (Vector CSigAtomic)
-> (Vector CSigAtomic -> Poke ())
-> Peek (Vector CSigAtomic)
-> Store (Vector CSigAtomic)
Size (Vector CClock)
-> (Vector CClock -> Poke ())
-> Peek (Vector CClock)
-> Store (Vector CClock)
Size (Vector CTime)
-> (Vector CTime -> Poke ())
-> Peek (Vector CTime)
-> Store (Vector CTime)
Size (Vector CUSeconds)
-> (Vector CUSeconds -> Poke ())
-> Peek (Vector CUSeconds)
-> Store (Vector CUSeconds)
Size (Vector CSUSeconds)
-> (Vector CSUSeconds -> Poke ())
-> Peek (Vector CSUSeconds)
-> Store (Vector CSUSeconds)
Size (Vector CIntPtr)
-> (Vector CIntPtr -> Poke ())
-> Peek (Vector CIntPtr)
-> Store (Vector CIntPtr)
Size (Vector CUIntPtr)
-> (Vector CUIntPtr -> Poke ())
-> Peek (Vector CUIntPtr)
-> Store (Vector CUIntPtr)
Size (Vector CIntMax)
-> (Vector CIntMax -> Poke ())
-> Peek (Vector CIntMax)
-> Store (Vector CIntMax)
Size (Vector CUIntMax)
-> (Vector CUIntMax -> Poke ())
-> Peek (Vector CUIntMax)
-> Store (Vector CUIntMax)
Size (Vector WordPtr)
-> (Vector WordPtr -> Poke ())
-> Peek (Vector WordPtr)
-> Store (Vector WordPtr)
Size (Vector IntPtr)
-> (Vector IntPtr -> Poke ())
-> Peek (Vector IntPtr)
-> Store (Vector IntPtr)
forall a. Peek (Vector (StablePtr a))
forall a. Peek (Vector (Ptr a))
forall a. Peek (Vector (FunPtr a))
forall a. Size (Vector (StablePtr a))
forall a. Size (Vector (Ptr a))
forall a. Size (Vector (FunPtr a))
forall a. Prim a => Peek (Vector (Min a))
forall a. Prim a => Peek (Vector (Max a))
forall a. Prim a => Peek (Vector (First a))
forall a. Prim a => Peek (Vector (Last a))
forall a. Prim a => Peek (Vector (Identity a))
forall a. Prim a => Peek (Vector (Dual a))
forall a. Prim a => Peek (Vector (Sum a))
forall a. Prim a => Peek (Vector (Product a))
forall a. Prim a => Peek (Vector (Down a))
forall a. Prim a => Size (Vector (Min a))
forall a. Prim a => Size (Vector (Max a))
forall a. Prim a => Size (Vector (First a))
forall a. Prim a => Size (Vector (Last a))
forall a. Prim a => Size (Vector (Identity a))
forall a. Prim a => Size (Vector (Dual a))
forall a. Prim a => Size (Vector (Sum a))
forall a. Prim a => Size (Vector (Product a))
forall a. Prim a => Size (Vector (Down a))
forall a. Prim a => Vector (Min a) -> Poke ()
forall a. Prim a => Vector (Max a) -> Poke ()
forall a. Prim a => Vector (First a) -> Poke ()
forall a. Prim a => Vector (Last a) -> Poke ()
forall a. Prim a => Vector (Identity a) -> Poke ()
forall a. Prim a => Vector (Dual a) -> Poke ()
forall a. Prim a => Vector (Sum a) -> Poke ()
forall a. Prim a => Vector (Product a) -> Poke ()
forall a. Prim a => Vector (Down a) -> Poke ()
forall a. Vector (StablePtr a) -> Poke ()
forall a. Vector (Ptr a) -> Poke ()
forall a. Vector (FunPtr a) -> Poke ()
forall a. Size a -> (a -> Poke ()) -> Peek a -> Store a
forall a b. Prim a => Peek (Vector (Const a b))
forall a b. Prim a => Size (Vector (Const a b))
forall a b. Prim a => Vector (Const a b) -> Poke ()
peek :: Peek (Vector (Const a b))
$cpeek :: forall a b. Prim a => Peek (Vector (Const a b))
poke :: Vector (Const a b) -> Poke ()
$cpoke :: forall a b. Prim a => Vector (Const a b) -> Poke ()
size :: Size (Vector (Const a b))
$csize :: forall a b. Prim a => Size (Vector (Const a b))
peek :: Peek (Vector (Identity a))
$cpeek :: forall a. Prim a => Peek (Vector (Identity a))
poke :: Vector (Identity a) -> Poke ()
$cpoke :: forall a. Prim a => Vector (Identity a) -> Poke ()
size :: Size (Vector (Identity a))
$csize :: forall a. Prim a => Size (Vector (Identity a))
peek :: Peek (Vector (Down a))
$cpeek :: forall a. Prim a => Peek (Vector (Down a))
poke :: Vector (Down a) -> Poke ()
$cpoke :: forall a. Prim a => Vector (Down a) -> Poke ()
size :: Size (Vector (Down a))
$csize :: forall a. Prim a => Size (Vector (Down a))
peek :: Peek (Vector (First a))
$cpeek :: forall a. Prim a => Peek (Vector (First a))
poke :: Vector (First a) -> Poke ()
$cpoke :: forall a. Prim a => Vector (First a) -> Poke ()
size :: Size (Vector (First a))
$csize :: forall a. Prim a => Size (Vector (First a))
peek :: Peek (Vector (Last a))
$cpeek :: forall a. Prim a => Peek (Vector (Last a))
poke :: Vector (Last a) -> Poke ()
$cpoke :: forall a. Prim a => Vector (Last a) -> Poke ()
size :: Size (Vector (Last a))
$csize :: forall a. Prim a => Size (Vector (Last a))
peek :: Peek (Vector (Max a))
$cpeek :: forall a. Prim a => Peek (Vector (Max a))
poke :: Vector (Max a) -> Poke ()
$cpoke :: forall a. Prim a => Vector (Max a) -> Poke ()
size :: Size (Vector (Max a))
$csize :: forall a. Prim a => Size (Vector (Max a))
peek :: Peek (Vector (Min a))
$cpeek :: forall a. Prim a => Peek (Vector (Min a))
poke :: Vector (Min a) -> Poke ()
$cpoke :: forall a. Prim a => Vector (Min a) -> Poke ()
size :: Size (Vector (Min a))
$csize :: forall a. Prim a => Size (Vector (Min a))
peek :: Peek (Vector (Dual a))
$cpeek :: forall a. Prim a => Peek (Vector (Dual a))
poke :: Vector (Dual a) -> Poke ()
$cpoke :: forall a. Prim a => Vector (Dual a) -> Poke ()
size :: Size (Vector (Dual a))
$csize :: forall a. Prim a => Size (Vector (Dual a))
peek :: Peek (Vector (Product a))
$cpeek :: forall a. Prim a => Peek (Vector (Product a))
poke :: Vector (Product a) -> Poke ()
$cpoke :: forall a. Prim a => Vector (Product a) -> Poke ()
size :: Size (Vector (Product a))
$csize :: forall a. Prim a => Size (Vector (Product a))
peek :: Peek (Vector (Sum a))
$cpeek :: forall a. Prim a => Peek (Vector (Sum a))
poke :: Vector (Sum a) -> Poke ()
$cpoke :: forall a. Prim a => Vector (Sum a) -> Poke ()
size :: Size (Vector (Sum a))
$csize :: forall a. Prim a => Size (Vector (Sum a))
peek :: Peek (Vector CBool)
$cpeek :: Peek (Vector CBool)
poke :: Vector CBool -> Poke ()
$cpoke :: Vector CBool -> Poke ()
size :: Size (Vector CBool)
$csize :: Size (Vector CBool)
peek :: Peek (Vector CChar)
$cpeek :: Peek (Vector CChar)
poke :: Vector CChar -> Poke ()
$cpoke :: Vector CChar -> Poke ()
size :: Size (Vector CChar)
$csize :: Size (Vector CChar)
peek :: Peek (Vector CClock)
$cpeek :: Peek (Vector CClock)
poke :: Vector CClock -> Poke ()
$cpoke :: Vector CClock -> Poke ()
size :: Size (Vector CClock)
$csize :: Size (Vector CClock)
peek :: Peek (Vector CDouble)
$cpeek :: Peek (Vector CDouble)
poke :: Vector CDouble -> Poke ()
$cpoke :: Vector CDouble -> Poke ()
size :: Size (Vector CDouble)
$csize :: Size (Vector CDouble)
peek :: Peek (Vector CFloat)
$cpeek :: Peek (Vector CFloat)
poke :: Vector CFloat -> Poke ()
$cpoke :: Vector CFloat -> Poke ()
size :: Size (Vector CFloat)
$csize :: Size (Vector CFloat)
peek :: Peek (Vector CInt)
$cpeek :: Peek (Vector CInt)
poke :: Vector CInt -> Poke ()
$cpoke :: Vector CInt -> Poke ()
size :: Size (Vector CInt)
$csize :: Size (Vector CInt)
peek :: Peek (Vector CIntMax)
$cpeek :: Peek (Vector CIntMax)
poke :: Vector CIntMax -> Poke ()
$cpoke :: Vector CIntMax -> Poke ()
size :: Size (Vector CIntMax)
$csize :: Size (Vector CIntMax)
peek :: Peek (Vector CIntPtr)
$cpeek :: Peek (Vector CIntPtr)
poke :: Vector CIntPtr -> Poke ()
$cpoke :: Vector CIntPtr -> Poke ()
size :: Size (Vector CIntPtr)
$csize :: Size (Vector CIntPtr)
peek :: Peek (Vector CLLong)
$cpeek :: Peek (Vector CLLong)
poke :: Vector CLLong -> Poke ()
$cpoke :: Vector CLLong -> Poke ()
size :: Size (Vector CLLong)
$csize :: Size (Vector CLLong)
peek :: Peek (Vector CLong)
$cpeek :: Peek (Vector CLong)
poke :: Vector CLong -> Poke ()
$cpoke :: Vector CLong -> Poke ()
size :: Size (Vector CLong)
$csize :: Size (Vector CLong)
peek :: Peek (Vector CPtrdiff)
$cpeek :: Peek (Vector CPtrdiff)
poke :: Vector CPtrdiff -> Poke ()
$cpoke :: Vector CPtrdiff -> Poke ()
size :: Size (Vector CPtrdiff)
$csize :: Size (Vector CPtrdiff)
peek :: Peek (Vector CSChar)
$cpeek :: Peek (Vector CSChar)
poke :: Vector CSChar -> Poke ()
$cpoke :: Vector CSChar -> Poke ()
size :: Size (Vector CSChar)
$csize :: Size (Vector CSChar)
peek :: Peek (Vector CSUSeconds)
$cpeek :: Peek (Vector CSUSeconds)
poke :: Vector CSUSeconds -> Poke ()
$cpoke :: Vector CSUSeconds -> Poke ()
size :: Size (Vector CSUSeconds)
$csize :: Size (Vector CSUSeconds)
peek :: Peek (Vector CShort)
$cpeek :: Peek (Vector CShort)
poke :: Vector CShort -> Poke ()
$cpoke :: Vector CShort -> Poke ()
size :: Size (Vector CShort)
$csize :: Size (Vector CShort)
peek :: Peek (Vector CSigAtomic)
$cpeek :: Peek (Vector CSigAtomic)
poke :: Vector CSigAtomic -> Poke ()
$cpoke :: Vector CSigAtomic -> Poke ()
size :: Size (Vector CSigAtomic)
$csize :: Size (Vector CSigAtomic)
peek :: Peek (Vector CSize)
$cpeek :: Peek (Vector CSize)
poke :: Vector CSize -> Poke ()
$cpoke :: Vector CSize -> Poke ()
size :: Size (Vector CSize)
$csize :: Size (Vector CSize)
peek :: Peek (Vector CTime)
$cpeek :: Peek (Vector CTime)
poke :: Vector CTime -> Poke ()
$cpoke :: Vector CTime -> Poke ()
size :: Size (Vector CTime)
$csize :: Size (Vector CTime)
peek :: Peek (Vector CUChar)
$cpeek :: Peek (Vector CUChar)
poke :: Vector CUChar -> Poke ()
$cpoke :: Vector CUChar -> Poke ()
size :: Size (Vector CUChar)
$csize :: Size (Vector CUChar)
peek :: Peek (Vector CUInt)
$cpeek :: Peek (Vector CUInt)
poke :: Vector CUInt -> Poke ()
$cpoke :: Vector CUInt -> Poke ()
size :: Size (Vector CUInt)
$csize :: Size (Vector CUInt)
peek :: Peek (Vector CUIntMax)
$cpeek :: Peek (Vector CUIntMax)
poke :: Vector CUIntMax -> Poke ()
$cpoke :: Vector CUIntMax -> Poke ()
size :: Size (Vector CUIntMax)
$csize :: Size (Vector CUIntMax)
peek :: Peek (Vector CUIntPtr)
$cpeek :: Peek (Vector CUIntPtr)
poke :: Vector CUIntPtr -> Poke ()
$cpoke :: Vector CUIntPtr -> Poke ()
size :: Size (Vector CUIntPtr)
$csize :: Size (Vector CUIntPtr)
peek :: Peek (Vector CULLong)
$cpeek :: Peek (Vector CULLong)
poke :: Vector CULLong -> Poke ()
$cpoke :: Vector CULLong -> Poke ()
size :: Size (Vector CULLong)
$csize :: Size (Vector CULLong)
peek :: Peek (Vector CULong)
$cpeek :: Peek (Vector CULong)
poke :: Vector CULong -> Poke ()
$cpoke :: Vector CULong -> Poke ()
size :: Size (Vector CULong)
$csize :: Size (Vector CULong)
peek :: Peek (Vector CUSeconds)
$cpeek :: Peek (Vector CUSeconds)
poke :: Vector CUSeconds -> Poke ()
$cpoke :: Vector CUSeconds -> Poke ()
size :: Size (Vector CUSeconds)
$csize :: Size (Vector CUSeconds)
peek :: Peek (Vector CUShort)
$cpeek :: Peek (Vector CUShort)
poke :: Vector CUShort -> Poke ()
$cpoke :: Vector CUShort -> Poke ()
size :: Size (Vector CUShort)
$csize :: Size (Vector CUShort)
peek :: Peek (Vector CWchar)
$cpeek :: Peek (Vector CWchar)
poke :: Vector CWchar -> Poke ()
$cpoke :: Vector CWchar -> Poke ()
size :: Size (Vector CWchar)
$csize :: Size (Vector CWchar)
peek :: Peek (Vector IntPtr)
$cpeek :: Peek (Vector IntPtr)
poke :: Vector IntPtr -> Poke ()
$cpoke :: Vector IntPtr -> Poke ()
size :: Size (Vector IntPtr)
$csize :: Size (Vector IntPtr)
peek :: Peek (Vector WordPtr)
$cpeek :: Peek (Vector WordPtr)
poke :: Vector WordPtr -> Poke ()
$cpoke :: Vector WordPtr -> Poke ()
size :: Size (Vector WordPtr)
$csize :: Size (Vector WordPtr)
peek :: Peek (Vector Int16)
$cpeek :: Peek (Vector Int16)
poke :: Vector Int16 -> Poke ()
$cpoke :: Vector Int16 -> Poke ()
size :: Size (Vector Int16)
$csize :: Size (Vector Int16)
peek :: Peek (Vector Int32)
$cpeek :: Peek (Vector Int32)
poke :: Vector Int32 -> Poke ()
$cpoke :: Vector Int32 -> Poke ()
size :: Size (Vector Int32)
$csize :: Size (Vector Int32)
peek :: Peek (Vector Int64)
$cpeek :: Peek (Vector Int64)
poke :: Vector Int64 -> Poke ()
$cpoke :: Vector Int64 -> Poke ()
size :: Size (Vector Int64)
$csize :: Size (Vector Int64)
peek :: Peek (Vector Int8)
$cpeek :: Peek (Vector Int8)
poke :: Vector Int8 -> Poke ()
$cpoke :: Vector Int8 -> Poke ()
size :: Size (Vector Int8)
$csize :: Size (Vector Int8)
peek :: Peek (Vector (FunPtr a))
$cpeek :: forall a. Peek (Vector (FunPtr a))
poke :: Vector (FunPtr a) -> Poke ()
$cpoke :: forall a. Vector (FunPtr a) -> Poke ()
size :: Size (Vector (FunPtr a))
$csize :: forall a. Size (Vector (FunPtr a))
peek :: Peek (Vector (Ptr a))
$cpeek :: forall a. Peek (Vector (Ptr a))
poke :: Vector (Ptr a) -> Poke ()
$cpoke :: forall a. Vector (Ptr a) -> Poke ()
size :: Size (Vector (Ptr a))
$csize :: forall a. Size (Vector (Ptr a))
peek :: Peek (Vector (StablePtr a))
$cpeek :: forall a. Peek (Vector (StablePtr a))
poke :: Vector (StablePtr a) -> Poke ()
$cpoke :: forall a. Vector (StablePtr a) -> Poke ()
size :: Size (Vector (StablePtr a))
$csize :: forall a. Size (Vector (StablePtr a))
peek :: Peek (Vector Word16)
$cpeek :: Peek (Vector Word16)
poke :: Vector Word16 -> Poke ()
$cpoke :: Vector Word16 -> Poke ()
size :: Size (Vector Word16)
$csize :: Size (Vector Word16)
peek :: Peek (Vector Word32)
$cpeek :: Peek (Vector Word32)
poke :: Vector Word32 -> Poke ()
$cpoke :: Vector Word32 -> Poke ()
size :: Size (Vector Word32)
$csize :: Size (Vector Word32)
peek :: Peek (Vector Word64)
$cpeek :: Peek (Vector Word64)
poke :: Vector Word64 -> Poke ()
$cpoke :: Vector Word64 -> Poke ()
size :: Size (Vector Word64)
$csize :: Size (Vector Word64)
peek :: Peek (Vector Word8)
$cpeek :: Peek (Vector Word8)
poke :: Vector Word8 -> Poke ()
$cpoke :: Vector Word8 -> Poke ()
size :: Size (Vector Word8)
$csize :: Size (Vector Word8)
peek :: Peek (Vector CBlkCnt)
$cpeek :: Peek (Vector CBlkCnt)
poke :: Vector CBlkCnt -> Poke ()
$cpoke :: Vector CBlkCnt -> Poke ()
size :: Size (Vector CBlkCnt)
$csize :: Size (Vector CBlkCnt)
peek :: Peek (Vector CBlkSize)
$cpeek :: Peek (Vector CBlkSize)
poke :: Vector CBlkSize -> Poke ()
$cpoke :: Vector CBlkSize -> Poke ()
size :: Size (Vector CBlkSize)
$csize :: Size (Vector CBlkSize)
peek :: Peek (Vector CCc)
$cpeek :: Peek (Vector CCc)
poke :: Vector CCc -> Poke ()
$cpoke :: Vector CCc -> Poke ()
size :: Size (Vector CCc)
$csize :: Size (Vector CCc)
peek :: Peek (Vector CClockId)
$cpeek :: Peek (Vector CClockId)
poke :: Vector CClockId -> Poke ()
$cpoke :: Vector CClockId -> Poke ()
size :: Size (Vector CClockId)
$csize :: Size (Vector CClockId)
peek :: Peek (Vector CDev)
$cpeek :: Peek (Vector CDev)
poke :: Vector CDev -> Poke ()
$cpoke :: Vector CDev -> Poke ()
size :: Size (Vector CDev)
$csize :: Size (Vector CDev)
peek :: Peek (Vector CFsBlkCnt)
$cpeek :: Peek (Vector CFsBlkCnt)
poke :: Vector CFsBlkCnt -> Poke ()
$cpoke :: Vector CFsBlkCnt -> Poke ()
size :: Size (Vector CFsBlkCnt)
$csize :: Size (Vector CFsBlkCnt)
peek :: Peek (Vector CFsFilCnt)
$cpeek :: Peek (Vector CFsFilCnt)
poke :: Vector CFsFilCnt -> Poke ()
$cpoke :: Vector CFsFilCnt -> Poke ()
size :: Size (Vector CFsFilCnt)
$csize :: Size (Vector CFsFilCnt)
peek :: Peek (Vector CGid)
$cpeek :: Peek (Vector CGid)
poke :: Vector CGid -> Poke ()
$cpoke :: Vector CGid -> Poke ()
size :: Size (Vector CGid)
$csize :: Size (Vector CGid)
peek :: Peek (Vector CId)
$cpeek :: Peek (Vector CId)
poke :: Vector CId -> Poke ()
$cpoke :: Vector CId -> Poke ()
size :: Size (Vector CId)
$csize :: Size (Vector CId)
peek :: Peek (Vector CIno)
$cpeek :: Peek (Vector CIno)
poke :: Vector CIno -> Poke ()
$cpoke :: Vector CIno -> Poke ()
size :: Size (Vector CIno)
$csize :: Size (Vector CIno)
peek :: Peek (Vector CKey)
$cpeek :: Peek (Vector CKey)
poke :: Vector CKey -> Poke ()
$cpoke :: Vector CKey -> Poke ()
size :: Size (Vector CKey)
$csize :: Size (Vector CKey)
peek :: Peek (Vector CMode)
$cpeek :: Peek (Vector CMode)
poke :: Vector CMode -> Poke ()
$cpoke :: Vector CMode -> Poke ()
size :: Size (Vector CMode)
$csize :: Size (Vector CMode)
peek :: Peek (Vector CNlink)
$cpeek :: Peek (Vector CNlink)
poke :: Vector CNlink -> Poke ()
$cpoke :: Vector CNlink -> Poke ()
size :: Size (Vector CNlink)
$csize :: Size (Vector CNlink)
peek :: Peek (Vector COff)
$cpeek :: Peek (Vector COff)
poke :: Vector COff -> Poke ()
$cpoke :: Vector COff -> Poke ()
size :: Size (Vector COff)
$csize :: Size (Vector COff)
peek :: Peek (Vector CPid)
$cpeek :: Peek (Vector CPid)
poke :: Vector CPid -> Poke ()
$cpoke :: Vector CPid -> Poke ()
size :: Size (Vector CPid)
$csize :: Size (Vector CPid)
peek :: Peek (Vector CRLim)
$cpeek :: Peek (Vector CRLim)
poke :: Vector CRLim -> Poke ()
$cpoke :: Vector CRLim -> Poke ()
size :: Size (Vector CRLim)
$csize :: Size (Vector CRLim)
peek :: Peek (Vector CSpeed)
$cpeek :: Peek (Vector CSpeed)
poke :: Vector CSpeed -> Poke ()
$cpoke :: Vector CSpeed -> Poke ()
size :: Size (Vector CSpeed)
$csize :: Size (Vector CSpeed)
peek :: Peek (Vector CSsize)
$cpeek :: Peek (Vector CSsize)
poke :: Vector CSsize -> Poke ()
$cpoke :: Vector CSsize -> Poke ()
size :: Size (Vector CSsize)
$csize :: Size (Vector CSsize)
peek :: Peek (Vector CTcflag)
$cpeek :: Peek (Vector CTcflag)
poke :: Vector CTcflag -> Poke ()
$cpoke :: Vector CTcflag -> Poke ()
size :: Size (Vector CTcflag)
$csize :: Size (Vector CTcflag)
peek :: Peek (Vector CTimer)
$cpeek :: Peek (Vector CTimer)
poke :: Vector CTimer -> Poke ()
$cpoke :: Vector CTimer -> Poke ()
size :: Size (Vector CTimer)
$csize :: Size (Vector CTimer)
peek :: Peek (Vector CUid)
$cpeek :: Peek (Vector CUid)
poke :: Vector CUid -> Poke ()
$cpoke :: Vector CUid -> Poke ()
size :: Size (Vector CUid)
$csize :: Size (Vector CUid)
peek :: Peek (Vector Fd)
$cpeek :: Peek (Vector Fd)
poke :: Vector Fd -> Poke ()
$cpoke :: Vector Fd -> Poke ()
size :: Size (Vector Fd)
$csize :: Size (Vector Fd)
peek :: Peek (Vector Char)
$cpeek :: Peek (Vector Char)
poke :: Vector Char -> Poke ()
$cpoke :: Vector Char -> Poke ()
size :: Size (Vector Char)
$csize :: Size (Vector Char)
peek :: Peek (Vector Double)
$cpeek :: Peek (Vector Double)
poke :: Vector Double -> Poke ()
$cpoke :: Vector Double -> Poke ()
size :: Size (Vector Double)
$csize :: Size (Vector Double)
peek :: Peek (Vector Float)
$cpeek :: Peek (Vector Float)
poke :: Vector Float -> Poke ()
$cpoke :: Vector Float -> Poke ()
size :: Size (Vector Float)
$csize :: Size (Vector Float)
peek :: Peek (Vector Int)
$cpeek :: Peek (Vector Int)
poke :: Vector Int -> Poke ()
$cpoke :: Vector Int -> Poke ()
size :: Size (Vector Int)
$csize :: Size (Vector Int)
peek :: Peek (Vector Word)
$cpeek :: Peek (Vector Word)
poke :: Vector Word -> Poke ()
$cpoke :: Vector Word -> Poke ()
size :: Size (Vector Word)
$csize :: Size (Vector Word)
deriveManyStorePrimVector)
$(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 (\name -> return (deriveGenericInstance [] (ConT name))))