{-# 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 #-}

-- | Internal API for the store package. The functions here which are
-- not re-exported by "Data.Store" are less likely to have stable APIs.
--
-- This module also defines most of the included 'Store' instances, for
-- types from the base package and other commonly used packages
-- (bytestring, containers, text, time, etc).
module Data.Store.Internal
    (
    -- * Encoding and decoding strict ByteStrings.
      encode,
      decode, decodeWith,
      decodeEx, decodeExWith, decodeExPortionWith
    , decodeIO, decodeIOWith, decodeIOPortionWith
    -- * Store class and related types.
    , Store(..), Poke, Peek, runPeek
    -- ** Exceptions thrown by Poke
    , PokeException(..), pokeException
    -- ** Exceptions thrown by Peek
    , PeekException(..), peekException, tooManyBytes
    -- ** Size type
    , Size(..)
    , getSize, getSizeWith
    , combineSize, combineSizeWith, addSize
    -- ** Store instances in terms of IsSequence
    , sizeSequence, pokeSequence, peekSequence
    -- ** Store instances in terms of IsSet
    , sizeSet, pokeSet, peekSet
    -- ** Store instances in terms of IsMap
    , sizeMap, pokeMap, peekMap
    -- *** Utilities for ordered maps
    , sizeOrdMap, pokeOrdMap, peekOrdMapWith
    -- ** Store instances in terms of IArray
    , sizeArray, pokeArray, peekArray
    -- ** Store instances in terms of Generic
    , GStoreSize, genericSize
    , GStorePoke, genericPoke
    , GStorePeek, genericPeek
    -- ** Peek utilities
    , skip, isolate
    , peekMagic
    -- ** Static Size type
    --
    -- This portion of the library is still work-in-progress.
    -- 'IsStaticSize' is only supported for strict ByteStrings, in order
    -- to support the use case of 'Tagged'.
    , IsStaticSize(..), StaticSize(..), toStaticSizeEx, liftStaticSize, staticByteStringExp
    ) where

import           Control.Applicative
import           Control.DeepSeq (NFData)
import           Control.Exception (throwIO)
import           Control.Monad (when)
import           Control.Monad.IO.Class (liftIO)
import qualified Data.Array.Unboxed as A
import qualified Data.ByteString as BS
import qualified Data.ByteString.Internal as BS
import qualified Data.ByteString.Lazy as LBS
import qualified Data.ByteString.Short.Internal as SBS
import           Data.Containers (IsMap, ContainerKey, MapValue, mapFromList, mapToList, IsSet, setFromList)
import           Data.Complex (Complex (..))
import           Data.Data (Data)
import           Data.Fixed (Fixed (..), Pico)
import           Data.Foldable (forM_, foldl')
import           Data.Functor.Contravariant
import           Data.Functor.Identity (Identity (..))
import           Data.HashMap.Strict (HashMap)
import           Data.HashSet (HashSet)
import           Data.Hashable (Hashable)
import           Data.Int
import           Data.IntMap (IntMap)
import qualified Data.IntMap.Strict as IntMap
import           Data.IntSet (IntSet)
import qualified Data.IntSet as IntSet
import qualified Data.List.NonEmpty as NE
import           Data.Map (Map)
import qualified Data.Map.Strict as Map
import           Data.MonoTraversable
import           Data.Monoid
import           Data.Orphans ()
import           Data.Primitive.ByteArray
import           Data.Proxy (Proxy(..))
import           Data.Sequence (Seq)
import           Data.Sequences (IsSequence, Index, replicateM)
import           Data.Set (Set)
import qualified Data.Set as Set
import           Data.Store.Impl
import           Data.Store.Core
import           Data.Store.TH.Internal
import qualified Data.Text as T
import qualified Data.Text.Array as TA
import qualified Data.Text.Foreign as T
import qualified Data.Text.Internal as T
import qualified Data.Time as Time
import qualified Data.Time.Clock.TAI as Time
import           Data.Typeable (Typeable)
import qualified Data.Vector as V
import qualified Data.Vector.Mutable as MV
import qualified Data.Vector.Storable as SV
import qualified Data.Vector.Storable.Mutable as MSV
import           Data.Void
import           Data.Word
import           Foreign.C.Types ()
import           Foreign.Ptr (plusPtr, minusPtr)
import           Foreign.Storable (Storable, sizeOf)
import           GHC.Generics (Generic)
import           GHC.Real (Ratio(..))
import           GHC.TypeLits
import           Instances.TH.Lift ()
import           Language.Haskell.TH
import           Language.Haskell.TH.Instances ()
import           Language.Haskell.TH.ReifyMany
import           Language.Haskell.TH.Syntax
import           Network.Socket (AddrInfo)
import           Numeric.Natural (Natural)
import           Prelude
import           TH.Derive

#if MIN_VERSION_time(1,8,0)
import qualified Data.Time.Clock.System as Time
#endif
#if MIN_VERSION_time(1,9,0)
import qualified Data.Time.Format.ISO8601 as Time
#endif
#if MIN_VERSION_time(1,11,0)
import qualified Data.Time.Calendar.Quarter as Time
import qualified Data.Time.Calendar.WeekDate as Time
#endif

#ifdef INTEGER_GMP
import qualified GHC.Integer.GMP.Internals as I
import           GHC.Types (Int (I#))
#else
import           GHC.Types (Word (W#))
import qualified GHC.Integer.Simple.Internals as I
#endif

-- Conditional import to avoid warning
#ifdef INTEGER_GMP
#if MIN_VERSION_integer_gmp(1,0,0)
import           GHC.Prim (sizeofByteArray#)
#endif
#endif

-- TODO: higher arities?  Limited now by Generics instances for tuples
$(return $ map deriveTupleStoreInstance [2..7])

$(deriveManyStoreFromStorable
  (\ty ->
    case ty of
      ConT n | elem n [''Char, ''Int, ''Int64, ''Word, ''Word8, ''Word32] -> True
      _ -> False
    ))

------------------------------------------------------------------------
-- Utilities for defining list-like 'Store' instances in terms of 'IsSequence'

-- | Implement 'size' for an 'IsSequence' of 'Store' instances.
--
-- Note that many monomorphic containers have more efficient
-- implementations (for example, via memcpy).
sizeSequence :: forall t. (IsSequence t, Store (Element t)) => Size t
sizeSequence :: forall t. (IsSequence t, Store (Element t)) => Size t
sizeSequence = forall a. (a -> Int) -> Size a
VarSize forall a b. (a -> b) -> a -> b
$ \t
t ->
    case forall a. Store a => Size a
size :: Size (Element t) of
        ConstSize Int
n -> Int
n forall a. Num a => a -> a -> a
* (forall mono. MonoFoldable mono => mono -> Int
olength t
t) forall a. Num a => a -> a -> a
+ forall a. Storable a => a -> Int
sizeOf (forall a. HasCallStack => a
undefined :: Int)
        VarSize Element t -> Int
f -> forall mono a.
MonoFoldable mono =>
(a -> Element mono -> a) -> a -> mono -> a
ofoldl' (\Int
acc Element t
x -> Int
acc forall a. Num a => a -> a -> a
+ Element t -> Int
f Element t
x) (forall a. Storable a => a -> Int
sizeOf (forall a. HasCallStack => a
undefined :: Int)) t
t
{-# INLINE sizeSequence #-}

-- | Implement 'poke' for an 'IsSequence' of 'Store' instances.
--
-- Note that many monomorphic containers have more efficient
-- implementations (for example, via memcpy).
pokeSequence :: (IsSequence t, Store (Element t)) => t -> Poke ()
pokeSequence :: forall t. (IsSequence t, Store (Element t)) => t -> Poke ()
pokeSequence t
t =
  do forall a. Storable a => a -> Poke ()
pokeStorable Int
len
     forall a. (PokeState -> Int -> IO (Int, a)) -> Poke a
Poke (\PokeState
ptr Int
offset ->
             do Int
offset' <-
                  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'',()
_) <- forall a. Poke a -> PokeState -> Int -> IO (Int, a)
runPoke (forall a. Store a => a -> Poke ()
poke Element t
a) PokeState
ptr Int
offset'
                                forall (m :: * -> *) a. Monad m => a -> m a
return Int
offset'')
                          Int
offset
                          t
t
                forall (m :: * -> *) a. Monad m => a -> m a
return (Int
offset',()))
  where len :: Int
len = forall mono. MonoFoldable mono => mono -> Int
olength t
t
{-# INLINE pokeSequence #-}

-- | Implement 'peek' for an 'IsSequence' of 'Store' instances.
--
-- Note that many monomorphic containers have more efficient
-- implementations (for example, via memcpy).
peekSequence :: (IsSequence t, Store (Element t), Index t ~ Int) => Peek t
peekSequence :: forall t.
(IsSequence t, Store (Element t), Index t ~ Int) =>
Peek t
peekSequence = do
    Int
len <- forall a. Store a => Peek a
peek
    forall seq (m :: * -> *).
(IsSequence seq, Monad m) =>
Index seq -> m (Element seq) -> m seq
replicateM Int
len forall a. Store a => Peek a
peek
{-# INLINE peekSequence #-}

------------------------------------------------------------------------
-- Utilities for defining list-like 'Store' instances in terms of 'IsSet'

-- | Implement 'size' for an 'IsSet' of 'Store' instances.
sizeSet :: forall t. (IsSet t, Store (Element t)) => Size t
sizeSet :: forall t. (IsSet t, Store (Element t)) => Size t
sizeSet = forall a. (a -> Int) -> Size a
VarSize forall a b. (a -> b) -> a -> b
$ \t
t ->
    case forall a. Store a => Size a
size :: Size (Element t) of
        ConstSize Int
n -> Int
n forall a. Num a => a -> a -> a
* (forall mono. MonoFoldable mono => mono -> Int
olength t
t) forall a. Num a => a -> a -> a
+ forall a. Storable a => a -> Int
sizeOf (forall a. HasCallStack => a
undefined :: Int)
        VarSize Element t -> Int
f -> forall mono a.
MonoFoldable mono =>
(a -> Element mono -> a) -> a -> mono -> a
ofoldl' (\Int
acc Element t
x -> Int
acc forall a. Num a => a -> a -> a
+ Element t -> Int
f Element t
x) (forall a. Storable a => a -> Int
sizeOf (forall a. HasCallStack => a
undefined :: Int)) t
t
{-# INLINE sizeSet #-}

-- | Implement 'poke' for an 'IsSequence' of 'Store' instances.
pokeSet :: (IsSet t, Store (Element t)) => t -> Poke ()
pokeSet :: forall t. (IsSet t, Store (Element t)) => t -> Poke ()
pokeSet t
t = do
    forall a. Storable a => a -> Poke ()
pokeStorable (forall mono. MonoFoldable mono => mono -> Int
olength t
t)
    forall mono (m :: * -> *).
(MonoFoldable mono, Applicative m) =>
(Element mono -> m ()) -> mono -> m ()
omapM_ forall a. Store a => a -> Poke ()
poke t
t
{-# INLINE pokeSet #-}

-- | Implement 'peek' for an 'IsSequence' of 'Store' instances.
peekSet :: (IsSet t, Store (Element t)) => Peek t
peekSet :: forall t. (IsSet t, Store (Element t)) => Peek t
peekSet = do
    Int
len <- forall a. Store a => Peek a
peek
    forall set. IsSet set => [Element set] -> set
setFromList forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall seq (m :: * -> *).
(IsSequence seq, Monad m) =>
Index seq -> m (Element seq) -> m seq
replicateM Int
len forall a. Store a => Peek a
peek
{-# INLINE peekSet #-}

------------------------------------------------------------------------
-- Utilities for defining list-like 'Store' instances in terms of a 'IsMap'

-- | Implement 'size' for an 'IsMap' of where both 'ContainerKey' and
-- 'MapValue' are 'Store' instances.
sizeMap
    :: forall t. (Store (ContainerKey t), Store (MapValue t), IsMap t)
    => Size t
sizeMap :: forall t.
(Store (ContainerKey t), Store (MapValue t), IsMap t) =>
Size t
sizeMap = forall a. (a -> Int) -> Size a
VarSize forall a b. (a -> b) -> a -> b
$ \t
t ->
    case (forall a. Store a => Size a
size :: Size (ContainerKey t), forall a. Store a => Size a
size :: Size (MapValue t)) of
        (ConstSize Int
nk, ConstSize Int
na) -> (Int
nk forall a. Num a => a -> a -> a
+ Int
na) forall a. Num a => a -> a -> a
* forall mono. MonoFoldable mono => mono -> Int
olength t
t forall a. Num a => a -> a -> a
+ forall a. Storable a => a -> Int
sizeOf (forall a. HasCallStack => a
undefined :: Int)
        (Size (ContainerKey t)
szk, Size (MapValue t)
sza) -> forall mono a.
MonoFoldable mono =>
(a -> Element mono -> a) -> a -> mono -> a
ofoldl' (\Int
acc (ContainerKey t
k, MapValue t
a) -> Int
acc forall a. Num a => a -> a -> a
+ forall a. Size a -> a -> Int
getSizeWith Size (ContainerKey t)
szk ContainerKey t
k forall a. Num a => a -> a -> a
+ forall a. Size a -> a -> Int
getSizeWith Size (MapValue t)
sza MapValue t
a)
                              (forall a. Storable a => a -> Int
sizeOf (forall a. HasCallStack => a
undefined :: Int))
                              (forall map. IsMap map => map -> [(ContainerKey map, MapValue map)]
mapToList t
t)
{-# INLINE sizeMap #-}

-- | Implement 'poke' for an 'IsMap' of where both 'ContainerKey' and
-- 'MapValue' are 'Store' instances.
pokeMap
    :: (Store (ContainerKey t), Store (MapValue t), IsMap t)
    => t
    -> Poke ()
pokeMap :: forall t.
(Store (ContainerKey t), Store (MapValue t), IsMap t) =>
t -> Poke ()
pokeMap = forall t. (IsSequence t, Store (Element t)) => t -> Poke ()
pokeSequence forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall map. IsMap map => map -> [(ContainerKey map, MapValue map)]
mapToList
{-# INLINE pokeMap #-}

-- | Implement 'peek' for an 'IsMap' of where both 'ContainerKey' and
-- 'MapValue' are 'Store' instances.
peekMap
    :: (Store (ContainerKey t), Store (MapValue t), IsMap t)
    => Peek t
peekMap :: forall t.
(Store (ContainerKey t), Store (MapValue t), IsMap t) =>
Peek t
peekMap = forall map. IsMap map => [(ContainerKey map, MapValue map)] -> map
mapFromList forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. Store a => Peek a
peek
{-# INLINE peekMap #-}

------------------------------------------------------------------------
-- Utilities for defining 'Store' instances for ordered containers like
-- 'IntMap' and 'Map'

-- | Marker for maps that are encoded in ascending order instead of the
-- descending order mistakenly implemented in 'peekMap' in store versions
-- < 0.4.
--
-- See https://github.com/fpco/store/issues/97.
markMapPokedInAscendingOrder :: Word32
markMapPokedInAscendingOrder :: Word32
markMapPokedInAscendingOrder = Word32
1217678090

-- | Ensure the presence of a given magic value.
--
-- Throws a 'PeekException' if the value isn't present.
peekMagic
    :: (Eq a, Show a, Store a)
    => String -> a -> Peek ()
peekMagic :: forall a. (Eq a, Show a, Store a) => String -> a -> Peek ()
peekMagic String
markedThing a
x = do
    a
x' <- forall a. Store a => Peek a
peek
    forall (f :: * -> *). Applicative f => Unlifted -> f () -> f ()
when (a
x' forall a. Eq a => a -> a -> Unlifted
/= a
x) forall a b. (a -> b) -> a -> b
$
        forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String
"Expected marker for " forall a. [a] -> [a] -> [a]
++ String
markedThing forall a. [a] -> [a] -> [a]
++ String
": " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show a
x forall a. [a] -> [a] -> [a]
++ String
" but got: " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show a
x')
{-# INLINE peekMagic #-}

-- | Like 'sizeMap' but should only be used for ordered containers where
-- 'Data.Containers.mapToList' returns an ascending list.
sizeOrdMap
    :: forall t.
       (Store (ContainerKey t), Store (MapValue t), IsMap t)
    => Size t
sizeOrdMap :: forall t.
(Store (ContainerKey t), Store (MapValue t), IsMap t) =>
Size t
sizeOrdMap =
    forall a b c. (c -> a) -> (c -> b) -> Size a -> Size b -> Size c
combineSizeWith (forall a b. a -> b -> a
const Word32
markMapPokedInAscendingOrder) forall a. a -> a
id forall a. Store a => Size a
size forall t.
(Store (ContainerKey t), Store (MapValue t), IsMap t) =>
Size t
sizeMap
{-# INLINE sizeOrdMap #-}

-- | Like 'pokeMap' but should only be used for ordered containers where
-- 'Data.Containers.mapToList' returns an ascending list.
pokeOrdMap
    :: (Store (ContainerKey t), Store (MapValue t), IsMap t)
    => t -> Poke ()
pokeOrdMap :: forall t.
(Store (ContainerKey t), Store (MapValue t), IsMap t) =>
t -> Poke ()
pokeOrdMap t
x = forall a. Store a => a -> Poke ()
poke Word32
markMapPokedInAscendingOrder forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall t.
(Store (ContainerKey t), Store (MapValue t), IsMap t) =>
t -> Poke ()
pokeMap t
x
{-# INLINE pokeOrdMap #-}

-- | Decode the results of 'pokeOrdMap' using a given function to construct
-- the map.
peekOrdMapWith
    :: (Store (ContainerKey t), Store (MapValue t))
    => ([(ContainerKey t, MapValue t)] -> t)
       -- ^ A function to construct the map from an ascending list such as
       -- 'Map.fromDistinctAscList'.
    -> Peek t
peekOrdMapWith :: forall t.
(Store (ContainerKey t), Store (MapValue t)) =>
([(ContainerKey t, MapValue t)] -> t) -> Peek t
peekOrdMapWith [(ContainerKey t, MapValue t)] -> t
f = do
    forall a. (Eq a, Show a, Store a) => String -> a -> Peek ()
peekMagic String
"ascending Map / IntMap" Word32
markMapPokedInAscendingOrder
    [(ContainerKey t, MapValue t)] -> t
f forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. Store a => Peek a
peek
{-# INLINE peekOrdMapWith #-}

------------------------------------------------------------------------
-- Utilities for implementing 'Store' instances for list-like mutable things

-- | Implementation of peek for mutable sequences. The user provides a
-- function for initializing the sequence and a function for mutating an
-- element at a particular index.
peekMutableSequence
    :: Store a
    => (Int -> IO r)
    -> (r -> Int -> a -> IO ())
    -> Peek r
peekMutableSequence :: forall a r.
Store a =>
(Int -> IO r) -> (r -> Int -> a -> IO ()) -> Peek r
peekMutableSequence Int -> IO r
new r -> Int -> a -> IO ()
write = do
    Int
n <- forall a. Store a => Peek a
peek
    r
mut <- forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (Int -> IO r
new Int
n)
    forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
t a -> (a -> m b) -> m ()
forM_ [Int
0..Int
nforall a. Num a => a -> a -> a
-Int
1] forall a b. (a -> b) -> a -> b
$ \Int
i -> forall a. Store a => Peek a
peek forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall b c a. (b -> c) -> (a -> b) -> a -> c
. r -> Int -> a -> IO ()
write r
mut Int
i
    forall (m :: * -> *) a. Monad m => a -> m a
return r
mut
{-# INLINE peekMutableSequence #-}

------------------------------------------------------------------------
-- Useful combinators

-- | Skip n bytes forward.
{-# INLINE skip #-}
skip :: Int -> Peek ()
skip :: Int -> Peek ()
skip Int
len = forall a. (PeekState -> Ptr Word8 -> IO (PeekResult a)) -> Peek a
Peek forall a b. (a -> b) -> a -> b
$ \PeekState
ps Ptr Word8
ptr -> do
    let ptr2 :: Ptr Word8
ptr2 = Ptr Word8
ptr forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
len
        remaining :: Int
remaining = PeekState -> Ptr Word8
peekStateEndPtr PeekState
ps forall a b. Ptr a -> Ptr b -> Int
`minusPtr` Ptr Word8
ptr
    forall (f :: * -> *). Applicative f => Unlifted -> f () -> f ()
when (Int
len forall a. Ord a => a -> a -> Unlifted
> Int
remaining) forall a b. (a -> b) -> a -> b
$ -- Do not perform the check on the new pointer, since it could have overflowed
        forall void. Int -> Int -> String -> IO void
tooManyBytes Int
len Int
remaining String
"skip"
    forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall a. Ptr Word8 -> a -> PeekResult a
PeekResult Ptr Word8
ptr2 ()

-- | Isolate the input to n bytes, skipping n bytes forward. Fails if @m@
-- advances the offset beyond the isolated region.
{-# INLINE isolate #-}
isolate :: Int -> Peek a -> Peek a
isolate :: forall a. Int -> Peek a -> Peek a
isolate Int
len Peek a
m = forall a. (PeekState -> Ptr Word8 -> IO (PeekResult a)) -> Peek a
Peek 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 forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
len
        remaining :: Int
remaining = Ptr Word8
end forall a b. Ptr a -> Ptr b -> Int
`minusPtr` Ptr Word8
ptr
    forall (f :: * -> *). Applicative f => Unlifted -> f () -> f ()
when (Int
len forall a. Ord a => a -> a -> Unlifted
> Int
remaining) forall a b. (a -> b) -> a -> b
$ -- Do not perform the check on the new pointer, since it could have overflowed
        forall void. Int -> Int -> String -> IO void
tooManyBytes Int
len Int
remaining String
"isolate"
    PeekResult Ptr Word8
ptr' a
x <- forall a. Peek a -> PeekState -> Ptr Word8 -> IO (PeekResult a)
runPeek Peek a
m PeekState
ps Ptr Word8
ptr
    forall (f :: * -> *). Applicative f => Unlifted -> f () -> f ()
when (Ptr Word8
ptr' forall a. Ord a => a -> a -> Unlifted
> Ptr Word8
end) forall a b. (a -> b) -> a -> b
$
        forall e a. Exception e => e -> IO a
throwIO forall a b. (a -> b) -> a -> b
$ Int -> Text -> PeekException
PeekException (Ptr Word8
ptr' forall a b. Ptr a -> Ptr b -> Int
`minusPtr` Ptr Word8
end) Text
"Overshot end of isolated bytes"
    forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall a. Ptr Word8 -> a -> PeekResult a
PeekResult Ptr Word8
ptr2 a
x

------------------------------------------------------------------------
-- Instances for types based on flat representations

instance Store a => Store (V.Vector a) where
    size :: Size (Vector a)
size = forall t. (IsSequence t, Store (Element t)) => Size t
sizeSequence
    poke :: Vector a -> Poke ()
poke = forall t. (IsSequence t, Store (Element t)) => t -> Poke ()
pokeSequence
    peek :: Peek (Vector a)
peek = forall (m :: * -> *) a.
PrimMonad m =>
MVector (PrimState m) a -> m (Vector a)
V.unsafeFreeze forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< forall a r.
Store a =>
(Int -> IO r) -> (r -> Int -> a -> IO ()) -> Peek r
peekMutableSequence forall (m :: * -> *) a.
PrimMonad m =>
Int -> m (MVector (PrimState m) a)
MV.new 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 = forall a. (a -> Int) -> Size a
VarSize forall a b. (a -> b) -> a -> b
$ \Vector a
x ->
        forall a. Storable a => a -> Int
sizeOf (forall a. HasCallStack => a
undefined :: Int) forall a. Num a => a -> a -> a
+
        forall a. Storable a => a -> Int
sizeOf (forall a. HasCallStack => a
undefined :: a) forall a. Num a => a -> a -> a
* 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) = forall a. Vector a -> (ForeignPtr a, Int)
SV.unsafeToForeignPtr0 Vector a
x
        forall a. Store a => a -> Poke ()
poke Int
len
        forall a. ForeignPtr a -> Int -> Int -> Poke ()
pokeFromForeignPtr ForeignPtr a
fptr Int
0 (forall a. Storable a => a -> Int
sizeOf (forall a. HasCallStack => a
undefined :: a) forall a. Num a => a -> a -> a
* Int
len)
    peek :: Peek (Vector a)
peek = do
        Int
len <- forall a. Store a => Peek a
peek
        ForeignPtr a
fp <- forall a. String -> Int -> Peek (ForeignPtr a)
peekToPlainForeignPtr String
"Data.Storable.Vector.Vector" (forall a. Storable a => a -> Int
sizeOf (forall a. HasCallStack => a
undefined :: a) forall a. Num a => a -> a -> a
* Int
len)
        forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ forall a (m :: * -> *).
(Storable a, PrimMonad m) =>
MVector (PrimState m) a -> m (Vector a)
SV.unsafeFreeze (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 = forall a. (a -> Int) -> Size a
VarSize forall a b. (a -> b) -> a -> b
$ \ByteString
x ->
        forall a. Storable a => a -> Int
sizeOf (forall a. HasCallStack => a
undefined :: 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
        forall a. Store a => a -> Poke ()
poke Int
sourceLength
        forall a. ForeignPtr a -> Int -> Int -> Poke ()
pokeFromForeignPtr ForeignPtr Word8
sourceFp Int
sourceOffset Int
sourceLength
    peek :: Peek ByteString
peek = do
        Int
len <- forall a. Store a => Peek a
peek
        ForeignPtr Word8
fp <- forall a. String -> Int -> Peek (ForeignPtr a)
peekToPlainForeignPtr String
"Data.ByteString.ByteString" Int
len
        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)
-- | Template Haskell Bytes are nearly identical to ByteString, but it
-- can't depend on ByteString.
instance Store Bytes where
    size :: Size Bytes
size = forall a. (a -> Int) -> Size a
VarSize forall a b. (a -> b) -> a -> b
$ \Bytes
x ->
        forall a. Storable a => a -> Int
sizeOf (forall a. HasCallStack => a
undefined :: Int) forall a. Num a => a -> a -> a
+
        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
        forall a. Store a => a -> Poke ()
poke Word
sourceLength
        forall a. ForeignPtr a -> Int -> Int -> Poke ()
pokeFromForeignPtr ForeignPtr Word8
sourceFp (forall a b. (Integral a, Num b) => a -> b
fromIntegral Word
sourceOffset) (forall a b. (Integral a, Num b) => a -> b
fromIntegral Word
sourceLength)
    peek :: Peek Bytes
peek = do
        Word
len <- forall a. Store a => Peek a
peek
        ForeignPtr Word8
fp <- forall a. String -> Int -> Peek (ForeignPtr a)
peekToPlainForeignPtr String
"Data.ByteString.ByteString" (forall a b. (Integral a, Num b) => a -> b
fromIntegral Word
len)
        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 = forall a. (a -> Int) -> Size a
VarSize forall a b. (a -> b) -> a -> b
$ \ShortByteString
x ->
         forall a. Storable a => a -> Int
sizeOf (forall a. HasCallStack => a
undefined :: 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
        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 <- forall a. Store a => Peek a
peek
        ByteArray ByteArray#
array <- String -> Int -> Peek ByteArray
peekToByteArray String
"Data.ByteString.Short.ShortByteString" Int
len
        forall (m :: * -> *) a. Monad m => a -> m a
return (ByteArray# -> ShortByteString
SBS.SBS ByteArray#
array)

instance Store LBS.ByteString where
    size :: Size ByteString
size = forall a. (a -> Int) -> Size a
VarSize forall a b. (a -> b) -> a -> b
$ \ByteString
x ->
         forall a. Storable a => a -> Int
sizeOf (forall a. HasCallStack => a
undefined :: Int)  forall a. Num a => a -> a -> a
+
         forall a b. (Integral a, Num b) => a -> b
fromIntegral (ByteString -> Int64
LBS.length ByteString
x)
    -- TODO: more efficient implementation that avoids the double copy
    poke :: ByteString -> Poke ()
poke = forall a. Store a => a -> Poke ()
poke forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> ByteString
LBS.toStrict
    peek :: Peek ByteString
peek = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ByteString -> ByteString
LBS.fromStrict forall a. Store a => Peek a
peek

instance Store T.Text where
#if MIN_VERSION_text(2,0,0)
    size = VarSize $ \x ->
        sizeOf (undefined :: Int) +
        T.lengthWord8 x
    poke x = do
        let !(T.Text (TA.ByteArray array) w8Off w8Len) = x
        poke w8Len
        pokeFromByteArray array w8Off w8Len
    peek = do
        w8Len <- peek
        ByteArray array <- peekToByteArray "Data.Text.Text" w8Len
        return (T.Text (TA.ByteArray array) 0 w8Len)
#else
    size :: Size Text
size = forall a. (a -> Int) -> Size a
VarSize forall a b. (a -> b) -> a -> b
$ \Text
x ->
        forall a. Storable a => a -> Int
sizeOf (forall a. HasCallStack => a
undefined :: Int) forall a. Num a => a -> a -> a
+
        Int
2 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
        forall a. Store a => a -> Poke ()
poke Int
w16Len
        ByteArray# -> Int -> Int -> Poke ()
pokeFromByteArray ByteArray#
array (Int
2 forall a. Num a => a -> a -> a
* Int
w16Off) (Int
2 forall a. Num a => a -> a -> a
* Int
w16Len)
    peek :: Peek Text
peek = do
        Int
w16Len <- forall a. Store a => Peek a
peek
        ByteArray ByteArray#
array <- String -> Int -> Peek ByteArray
peekToByteArray String
"Data.Text.Text" (Int
2 forall a. Num a => a -> a -> a
* Int
w16Len)
        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)
#endif

------------------------------------------------------------------------
-- Known size instances

newtype StaticSize (n :: Nat) a = StaticSize { forall (n :: Nat) a. StaticSize n a -> a
unStaticSize :: a }
    deriving (StaticSize n a -> StaticSize n a -> Unlifted
forall (n :: Nat) a.
Eq a =>
StaticSize n a -> StaticSize n a -> Unlifted
forall a. (a -> a -> Unlifted) -> (a -> a -> Unlifted) -> Eq a
/= :: StaticSize n a -> StaticSize n a -> Unlifted
$c/= :: forall (n :: Nat) a.
Eq a =>
StaticSize n a -> StaticSize n a -> Unlifted
== :: StaticSize n a -> StaticSize n a -> Unlifted
$c== :: forall (n :: Nat) a.
Eq a =>
StaticSize n a -> StaticSize n a -> Unlifted
Eq, Int -> StaticSize n a -> ShowS
forall (n :: Nat) a. Show a => Int -> StaticSize n a -> ShowS
forall (n :: Nat) a. Show a => [StaticSize n a] -> ShowS
forall (n :: Nat) a. Show a => StaticSize n a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [StaticSize n a] -> ShowS
$cshowList :: forall (n :: Nat) a. Show a => [StaticSize n a] -> ShowS
show :: StaticSize n a -> String
$cshow :: forall (n :: Nat) a. Show a => StaticSize n a -> String
showsPrec :: Int -> StaticSize n a -> ShowS
$cshowsPrec :: forall (n :: Nat) a. Show a => Int -> StaticSize n a -> ShowS
Show, StaticSize n a -> StaticSize n a -> Unlifted
StaticSize n a -> StaticSize n a -> Ordering
StaticSize n a -> StaticSize n a -> StaticSize n a
forall {n :: Nat} {a}. Ord a => Eq (StaticSize n a)
forall (n :: Nat) a.
Ord a =>
StaticSize n a -> StaticSize n a -> Unlifted
forall (n :: Nat) a.
Ord a =>
StaticSize n a -> StaticSize n a -> Ordering
forall (n :: Nat) a.
Ord a =>
StaticSize n a -> StaticSize n a -> StaticSize n a
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Unlifted)
-> (a -> a -> Unlifted)
-> (a -> a -> Unlifted)
-> (a -> a -> Unlifted)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord 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 -> Unlifted
$c>= :: forall (n :: Nat) a.
Ord a =>
StaticSize n a -> StaticSize n a -> Unlifted
> :: StaticSize n a -> StaticSize n a -> Unlifted
$c> :: forall (n :: Nat) a.
Ord a =>
StaticSize n a -> StaticSize n a -> Unlifted
<= :: StaticSize n a -> StaticSize n a -> Unlifted
$c<= :: forall (n :: Nat) a.
Ord a =>
StaticSize n a -> StaticSize n a -> Unlifted
< :: StaticSize n a -> StaticSize n a -> Unlifted
$c< :: forall (n :: Nat) a.
Ord a =>
StaticSize n a -> StaticSize n a -> Unlifted
compare :: StaticSize n a -> StaticSize n a -> Ordering
$ccompare :: forall (n :: Nat) a.
Ord a =>
StaticSize n a -> StaticSize n a -> Ordering
Ord, StaticSize n a -> DataType
StaticSize n a -> Constr
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 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 (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)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> StaticSize n a -> m (StaticSize n a)
$cgmapMo :: forall (n :: Nat) a (m :: * -> *).
(KnownNat n, Data a, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> StaticSize n a -> m (StaticSize n a)
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> StaticSize n a -> m (StaticSize n a)
$cgmapMp :: forall (n :: Nat) a (m :: * -> *).
(KnownNat n, Data a, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> StaticSize n a -> m (StaticSize n a)
gmapM :: forall (m :: * -> *).
Monad m =>
(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 :: forall u.
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 u. (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 :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> StaticSize n a -> r
$cgmapQr :: forall (n :: Nat) a r r'.
(KnownNat n, Data a) =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> StaticSize n a -> r
gmapQl :: forall r r'.
(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 (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(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 (t :: * -> *) (c :: * -> *).
Typeable t =>
(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 (c :: * -> *).
(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 (c :: * -> *).
(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)
Data, Typeable, forall (n :: Nat) a x. Rep (StaticSize n a) x -> StaticSize n a
forall (n :: Nat) a x. StaticSize n a -> Rep (StaticSize n a) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$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 :: forall (n :: Nat) a. IsStaticSize n a => a -> StaticSize n a
toStaticSizeEx a
x =
    case 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 -> 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 forall a. Eq a => a -> a -> Unlifted
== forall a. Num a => Integer -> a
fromInteger (forall (n :: Nat) (proxy :: Nat -> *).
KnownNat n =>
proxy n -> Integer
natVal (forall {k} (t :: k). Proxy t
Proxy :: Proxy n)) = forall a. a -> Maybe a
Just (forall (n :: Nat) a. a -> StaticSize n a
StaticSize ByteString
bs)
        | Unlifted
otherwise = forall a. Maybe a
Nothing

instance KnownNat n => Store (StaticSize n BS.ByteString) where
    size :: Size (StaticSize n ByteString)
size = forall a. Int -> Size a
ConstSize (forall a. Num a => Integer -> a
fromInteger (forall (n :: Nat) (proxy :: Nat -> *).
KnownNat n =>
proxy n -> Integer
natVal (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
        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 = forall a. Num a => Integer -> a
fromInteger (forall (n :: Nat) (proxy :: Nat -> *).
KnownNat n =>
proxy n -> Integer
natVal (forall {k} (t :: k). Proxy t
Proxy :: Proxy n))
        ForeignPtr Word8
fp <- forall a. String -> Int -> Peek (ForeignPtr a)
peekToPlainForeignPtr (String
"StaticSize " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show Int
len forall a. [a] -> [a] -> [a]
++ String
" Data.ByteString.ByteString") Int
len
        forall (m :: * -> *) a. Monad m => a -> m a
return (forall (n :: Nat) a. a -> StaticSize n a
StaticSize (ForeignPtr Word8 -> Int -> Int -> ByteString
BS.PS ForeignPtr Word8
fp Int
0 Int
len))

-- NOTE: this could be a 'Lift' instance, but we can't use type holes in
-- TH. Alternatively we'd need a (TypeRep -> Type) function and Typeable
-- constraint.
liftStaticSize :: forall n a. (KnownNat n, Lift a) => TypeQ -> StaticSize n a -> ExpQ
liftStaticSize :: forall (n :: Nat) a.
(KnownNat n, Lift a) =>
TypeQ -> StaticSize n a -> ExpQ
liftStaticSize TypeQ
tyq (StaticSize a
x) = do
    let numTy :: TypeQ
numTy = forall (m :: * -> *). Quote m => m TyLit -> m Type
litT forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *). Quote m => Integer -> m TyLit
numTyLit forall a b. (a -> b) -> a -> b
$ forall (n :: Nat) (proxy :: Nat -> *).
KnownNat n =>
proxy n -> Integer
natVal (forall {k} (t :: k). Proxy t
Proxy :: Proxy n)
    [| StaticSize $(lift x) :: StaticSize $(numTy) $(tyq) |]

#if MIN_VERSION_template_haskell(2,17,0)
staticByteStringExp :: Quote m => BS.ByteString -> m Exp
#else
staticByteStringExp :: BS.ByteString -> ExpQ
#endif
staticByteStringExp :: forall (m :: * -> *). Quote m => ByteString -> m Exp
staticByteStringExp ByteString
bs =
    [| StaticSize bs :: StaticSize $(litT (numTyLit (fromIntegral len))) BS.ByteString |]
  where
    len :: Int
len = ByteString -> Int
BS.length ByteString
bs

------------------------------------------------------------------------
-- containers instances

instance Store a => Store [a] where
    size :: Size [a]
size = forall t. (IsSequence t, Store (Element t)) => Size t
sizeSequence
    poke :: [a] -> Poke ()
poke = forall t. (IsSequence t, Store (Element t)) => t -> Poke ()
pokeSequence
    peek :: Peek [a]
peek = 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 = forall t. (IsSequence t, Store (Element t)) => Size t
sizeSequence
    poke :: Seq a -> Poke ()
poke = forall t. (IsSequence t, Store (Element t)) => t -> Poke ()
pokeSequence
    peek :: Peek (Seq a)
peek = 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 =
        forall a. (a -> Int) -> Size a
VarSize forall a b. (a -> b) -> a -> b
$ \Set a
t ->
            forall a. Storable a => a -> Int
sizeOf (forall a. HasCallStack => a
undefined :: Int) forall a. Num a => a -> a -> a
+
            case forall a. Store a => Size a
size of
                ConstSize Int
n -> Int
n forall a. Num a => a -> a -> a
* forall a. Set a -> Int
Set.size Set a
t
                VarSize a -> Int
f -> forall a b. (a -> b -> a) -> a -> Set b -> a
Set.foldl' (\Int
acc a
a -> Int
acc forall a. Num a => a -> a -> a
+ a -> Int
f a
a) Int
0 Set a
t
    poke :: Set a -> Poke ()
poke = forall t. (IsSet t, Store (Element t)) => t -> Poke ()
pokeSet
    peek :: Peek (Set a)
peek = forall a. [a] -> Set a
Set.fromDistinctAscList forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. Store a => Peek a
peek

instance Store IntSet where
    size :: Size IntSet
size = forall t. (IsSet t, Store (Element t)) => Size t
sizeSet
    poke :: IntSet -> Poke ()
poke = forall t. (IsSet t, Store (Element t)) => t -> Poke ()
pokeSet
    peek :: Peek IntSet
peek = [Int] -> IntSet
IntSet.fromDistinctAscList forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. Store a => Peek a
peek

instance Store a => Store (IntMap a) where
    size :: Size (IntMap a)
size = forall t.
(Store (ContainerKey t), Store (MapValue t), IsMap t) =>
Size t
sizeOrdMap
    poke :: IntMap a -> Poke ()
poke = forall t.
(Store (ContainerKey t), Store (MapValue t), IsMap t) =>
t -> Poke ()
pokeOrdMap
    peek :: Peek (IntMap a)
peek = forall t.
(Store (ContainerKey t), Store (MapValue t)) =>
([(ContainerKey t, MapValue t)] -> t) -> Peek t
peekOrdMapWith 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 =
        forall a. (a -> Int) -> Size a
VarSize forall a b. (a -> b) -> a -> b
$ \Map k a
t ->
            forall a. Storable a => a -> Int
sizeOf Word32
markMapPokedInAscendingOrder forall a. Num a => a -> a -> a
+ forall a. Storable a => a -> Int
sizeOf (forall a. HasCallStack => a
undefined :: Int) forall a. Num a => a -> a -> a
+
            case (forall a. Store a => Size a
size, forall a. Store a => Size a
size) of
                (ConstSize Int
nk, ConstSize Int
na) -> (Int
nk forall a. Num a => a -> a -> a
+ Int
na) forall a. Num a => a -> a -> a
* forall k a. Map k a -> Int
Map.size Map k a
t
                (Size k
szk, Size a
sza) ->
                    forall a k b. (a -> k -> b -> a) -> a -> Map k b -> a
Map.foldlWithKey'
                        (\Int
acc k
k a
a -> Int
acc forall a. Num a => a -> a -> a
+ forall a. Size a -> a -> Int
getSizeWith Size k
szk k
k forall a. Num a => a -> a -> a
+ forall a. Size a -> a -> Int
getSizeWith Size a
sza a
a)
                        Int
0
                        Map k a
t
    poke :: Map k a -> Poke ()
poke = forall t.
(Store (ContainerKey t), Store (MapValue t), IsMap t) =>
t -> Poke ()
pokeOrdMap
    peek :: Peek (Map k a)
peek = forall t.
(Store (ContainerKey t), Store (MapValue t)) =>
([(ContainerKey t, MapValue t)] -> t) -> Peek t
peekOrdMapWith 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 = forall t.
(Store (ContainerKey t), Store (MapValue t), IsMap t) =>
Size t
sizeMap
    poke :: HashMap k a -> Poke ()
poke = forall t.
(Store (ContainerKey t), Store (MapValue t), IsMap t) =>
t -> Poke ()
pokeMap
    peek :: Peek (HashMap k a)
peek = 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 = forall t. (IsSet t, Store (Element t)) => Size t
sizeSet
    poke :: HashSet a -> Poke ()
poke = forall t. (IsSet t, Store (Element t)) => t -> Poke ()
pokeSet
    peek :: Peek (HashSet a)
peek = 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 = forall i (a :: * -> * -> *) e.
(Ix i, IArray a e, Store i, Store e) =>
Size (a i e)
sizeArray
    poke :: Array i e -> Poke ()
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 = 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 = forall i (a :: * -> * -> *) e.
(Ix i, IArray a e, Store i, Store e) =>
Size (a i e)
sizeArray
    poke :: UArray i e -> Poke ()
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 = forall i (a :: * -> * -> *) e.
(Ix i, IArray a e, Store i, Store e) =>
Peek (a i e)
peekArray

sizeArray :: (A.Ix i, A.IArray a e, Store i, Store e) => Size (a i e)
sizeArray :: forall i (a :: * -> * -> *) e.
(Ix i, IArray a e, Store i, Store e) =>
Size (a i e)
sizeArray = forall a. (a -> Int) -> Size a
VarSize forall a b. (a -> b) -> a -> b
$ \a i e
arr ->
    let bounds :: (i, i)
bounds = forall (a :: * -> * -> *) e i.
(IArray a e, Ix i) =>
a i e -> (i, i)
A.bounds a i e
arr
    in  forall a. Store a => a -> Int
getSize (i, i)
bounds forall a. Num a => a -> a -> a
+
        case forall a. Store a => Size a
size of
            ConstSize Int
n ->  Int
n forall a. Num a => a -> a -> a
* forall a. Ix a => (a, a) -> Int
A.rangeSize (i, i)
bounds
            VarSize e -> Int
f -> forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' (\Int
acc e
x -> Int
acc forall a. Num a => a -> a -> a
+ e -> Int
f e
x) Int
0 (forall (a :: * -> * -> *) e i. (IArray a e, Ix i) => a i e -> [e]
A.elems a i e
arr)
{-# INLINE sizeArray #-}

pokeArray :: (A.Ix i, A.IArray a e, Store i, Store e) => a i e -> Poke ()
pokeArray :: forall i (a :: * -> * -> *) e.
(Ix i, IArray a e, Store i, Store e) =>
a i e -> Poke ()
pokeArray a i e
arr = do
    forall a. Store a => a -> Poke ()
poke (forall (a :: * -> * -> *) e i.
(IArray a e, Ix i) =>
a i e -> (i, i)
A.bounds a i e
arr)
    forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
t a -> (a -> m b) -> m ()
forM_ (forall (a :: * -> * -> *) e i. (IArray a e, Ix i) => a i e -> [e]
A.elems a i e
arr) forall a. Store a => a -> Poke ()
poke
{-# INLINE pokeArray #-}

peekArray :: (A.Ix i, A.IArray a e, Store i, Store e) => Peek (a i e)
peekArray :: forall i (a :: * -> * -> *) e.
(Ix i, IArray a e, Store i, Store e) =>
Peek (a i e)
peekArray = do
    (i, i)
bounds <- forall a. Store a => Peek a
peek
    let len :: Int
len = forall a. Ix a => (a, a) -> Int
A.rangeSize (i, i)
bounds
    [e]
elems <- forall seq (m :: * -> *).
(IsSequence seq, Monad m) =>
Index seq -> m (Element seq) -> m seq
replicateM Int
len forall a. Store a => Peek a
peek
    forall (m :: * -> *) a. Monad m => a -> m a
return (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 = forall a. (a -> Int) -> Size a
VarSize forall a b. (a -> b) -> a -> b
$ \ Integer
x ->
        forall a. Storable a => a -> Int
sizeOf (forall a. HasCallStack => a
undefined :: Word8) forall a. Num a => a -> a -> a
+ case Integer
x of
            I.S# Int#
_ -> forall a. Storable a => a -> Int
sizeOf (forall a. HasCallStack => a
undefined :: Int)
            I.Jp# (I.BN# ByteArray#
arr) -> forall a. Storable a => a -> Int
sizeOf (forall a. HasCallStack => a
undefined :: Int) forall a. Num a => a -> a -> a
+ Int# -> Int
I# (ByteArray# -> Int#
sizeofByteArray# ByteArray#
arr)
            I.Jn# (I.BN# ByteArray#
arr) -> forall a. Storable a => a -> Int
sizeOf (forall a. HasCallStack => a
undefined :: Int) forall a. Num a => a -> a -> a
+ Int# -> Int
I# (ByteArray# -> Int#
sizeofByteArray# ByteArray#
arr)
    poke :: Integer -> Poke ()
poke (I.S# Int#
x) = forall a. Store a => a -> Poke ()
poke (Word8
0 :: Word8) forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> 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)
        forall a. Store a => a -> Poke ()
poke (Word8
1 :: Word8)
        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)
        forall a. Store a => a -> Poke ()
poke (Word8
2 :: Word8)
        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 <- forall a. Store a => Peek a
peek :: Peek Word8
        case Word8
tag of
            Word8
0 -> forall a b. (Integral a, Num b) => a -> b
fromIntegral forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall a. Store a => Peek a
peek :: Peek Int)
            Word8
1 -> BigNat -> Integer
I.Jp# forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Peek BigNat
peekBN
            Word8
2 -> BigNat -> Integer
I.Jn# forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Peek BigNat
peekBN
            Word8
_ -> forall a. Text -> Peek a
peekException Text
"Invalid Integer tag"
      where
        peekBN :: Peek BigNat
peekBN = do
          Int
len <- forall a. Store a => Peek a
peek :: Peek Int
          ByteArray ByteArray#
arr <- String -> Int -> Peek ByteArray
peekToByteArray String
"GHC>Integer" Int
len
          forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ ByteArray# -> BigNat
I.BN# ByteArray#
arr
#else
    -- May as well put in the extra effort to use the same encoding as
    -- used for the newer integer-gmp.
    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
    -- NOTE: integer-simple uses a different encoding than GMP
    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

-- Piggybacks off of the Integer instance

instance Store Natural where
  size :: Size Nat
size = forall (f :: * -> *) a' a.
Contravariant f =>
(a' -> a) -> f a -> f a'
contramap forall a b. (Integral a, Num b) => a -> b
fromIntegral (forall a. Store a => Size a
size :: Size Integer)
  poke :: Nat -> Poke ()
poke = forall a. Store a => a -> Poke ()
poke forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Integral a => a -> Integer
toInteger
  peek :: Peek Nat
peek = do
      Integer
x <- forall a. Store a => Peek a
peek :: Peek Integer
      if Integer
x forall a. Ord a => a -> a -> Unlifted
< Integer
0
          then forall a. Text -> Peek a
peekException Text
"Encountered negative integer when expecting a Natural"
          else forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
x

------------------------------------------------------------------------
-- Other instances

-- Manual implementation due to no Generic instance for Ratio. Also due
-- to the instance for Storable erroring when the denominator is 0.
-- Perhaps we should keep the behavior but instead a peekException?
--
-- In that case it should also error on poke.
--
-- I prefer being able to Store these, because they are constructable.

instance Store a => Store (Ratio a) where
    size :: Size (Ratio a)
size = 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) = forall a. Store a => a -> Poke ()
poke (a
x, a
y)
    peek :: Peek (Ratio a)
peek = forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry forall a. a -> a -> Ratio a
(:%) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. Store a => Peek a
peek

-- Similarly, manual implementation due to no Generic instance for
-- Complex and Identity in GHC-7.10 and earlier.

$($(derive [d| instance Deriving (Store (Fixed a)) |]))

instance Store Time.DiffTime where
    size :: Size DiffTime
size = forall (f :: * -> *) a' a.
Contravariant f =>
(a' -> a) -> f a -> f a'
contramap (forall a b. (Real a, Fractional b) => a -> b
realToFrac :: Time.DiffTime -> Pico) forall a. Store a => Size a
size
    poke :: DiffTime -> Poke ()
poke = forall a. Store a => a -> Poke ()
poke forall b c a. (b -> c) -> (a -> b) -> a -> c
. (forall a b. (Real a, Fractional b) => a -> b
realToFrac :: Time.DiffTime -> Pico)
    peek :: Peek DiffTime
peek = (forall a b. (Real a, Fractional b) => a -> b
realToFrac :: Pico -> Time.DiffTime) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. Store a => Peek a
peek

instance Store Time.NominalDiffTime where
    size :: Size NominalDiffTime
size = forall (f :: * -> *) a' a.
Contravariant f =>
(a' -> a) -> f a -> f a'
contramap (forall a b. (Real a, Fractional b) => a -> b
realToFrac :: Time.NominalDiffTime -> Pico) forall a. Store a => Size a
size
    poke :: NominalDiffTime -> Poke ()
poke = forall a. Store a => a -> Poke ()
poke forall b c a. (b -> c) -> (a -> b) -> a -> c
. (forall a b. (Real a, Fractional b) => a -> b
realToFrac :: Time.NominalDiffTime -> Pico)
    peek :: Peek NominalDiffTime
peek = (forall a b. (Real a, Fractional b) => a -> b
realToFrac :: Pico -> Time.NominalDiffTime) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> 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)

------------------------------------------------------------------------
-- Instances generated by TH

$($(derive [d|
    instance Store a => Deriving (Store (Complex a))
    instance Store a => Deriving (Store (Identity a))

    instance Deriving (Store All)
    instance Deriving (Store Any)
    instance Deriving (Store Void)
    instance Deriving (Store Bool)
    instance (Store a, Store b) => Deriving (Store (Either a b))

    instance Deriving (Store Time.AbsoluteTime)
    instance Deriving (Store Time.Day)
    instance Deriving (Store Time.LocalTime)
    instance Deriving (Store Time.TimeOfDay)
    instance Deriving (Store Time.TimeZone)
    instance Deriving (Store Time.UTCTime)
    instance Deriving (Store Time.UniversalTime)
    instance Deriving (Store Time.ZonedTime)
    instance Deriving (Store Time.TimeLocale)

#if MIN_VERSION_time(1,8,0)
    instance Deriving (Store Time.SystemTime)
#endif

#if MIN_VERSION_time(1,9,0)
    instance Deriving (Store Time.CalendarDiffDays)
    instance Deriving (Store Time.CalendarDiffTime)
    instance Deriving (Store Time.FormatExtension)
#endif

#if MIN_VERSION_time(1,11,0)
    instance Deriving (Store Time.DayOfWeek)
    instance Deriving (Store Time.FirstWeekType)
    instance Deriving (Store Time.Quarter)
    instance Deriving (Store Time.QuarterOfYear)
#endif

    |]))

$(deriveManyStorePrimVector)

$(deriveManyStoreUnboxVector)

$(deriveManyStoreFromStorable
  -- TODO: Figure out why on GHC-8.2.1 this internal datatype is visible
  -- in the instances of Storable. Here's a gist of an attempt at
  -- debugging the issue:
  --
  -- https://gist.github.com/mgsloan/a7c416b961015949d3b5674ce053bbf6
  --
  -- The mysterious thing is why this is happening despite not having a
  -- direct import of Data.Text.Encoding.
  (\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
      -- AddrInfo's Storable instance is lossy, so avoid having a Store
      -- instance for it.
      ConT n | n == ''AddrInfo -> False
      _ -> True
    ))

$(reifyManyWithoutInstances ''Store [''ModName, ''NameSpace, ''PkgName] (const True) >>=
   mapM (\name -> return (deriveGenericInstance [] (ConT name))))

-- Explicit definition needed because in template-haskell <= 2.9 (GHC
-- 7.8), NameFlavour contains unboxed values, causing generic deriving
-- to fail.
#if !MIN_VERSION_template_haskell(2,10,0)
instance Store NameFlavour where
    size = VarSize $ \x -> getSize (0 :: Word8) + case x of
        NameS -> 0
        NameQ mn -> getSize mn
        NameU i -> getSize (I# i)
        NameL i -> getSize (I# i)
        NameG ns pn mn -> getSize ns + getSize pn + getSize mn
    poke NameS = poke (0 :: Word8)
    poke (NameQ mn) = do
        poke (1 :: Word8)
        poke mn
    poke (NameU i) = do
        poke (2 :: Word8)
        poke (I# i)
    poke (NameL i) = do
        poke (3 :: Word8)
        poke (I# i)
    poke (NameG ns pn mn) = do
        poke (4 :: Word8)
        poke ns
        poke pn
        poke mn
    peek = do
        tag <- peek
        case tag :: Word8 of
            0 -> return NameS
            1 -> NameQ <$> peek
            2 -> do
                !(I# i) <- peek
                return (NameU i)
            3 -> do
                !(I# i) <- peek
                return (NameL i)
            4 -> NameG <$> peek <*> peek <*> peek
            _ -> peekException "Invalid NameFlavour tag"
#endif

$(reifyManyWithoutInstances ''Store [''Info] (const True) >>=
   mapM deriveGenericInstanceFromName)