Move the Array serialization APIs to the Array module

This commit is contained in:
Harendra Kumar 2023-11-25 10:19:13 +05:30
parent 56fd008519
commit 7cb856b7e6
5 changed files with 69 additions and 67 deletions

View File

@ -24,7 +24,7 @@ import System.Random (randomRIO)
import Test.QuickCheck (Arbitrary, arbitrary)
#endif
import Streamly.Internal.Data.MutByteArray hiding (encode)
import Streamly.Internal.Data.MutByteArray
import qualified Streamly.Internal.Data.MutByteArray as MBA
#ifdef USE_UNBOX
import Data.Proxy (Proxy(..))

View File

@ -5,17 +5,24 @@
-- Maintainer : streamly@composewell.com
-- Portability : GHC
--
-- Fast binary serialization and deserialization of Haskell values to and from
-- arrays. This module provides two type classes for serialization, 'Unbox' and
-- A low level byte Array type for fast binary serialization and
-- deserialization of Haskell values. Higher level unboxed array modules
-- "Streamly.Data.Array" and "Streamly.Data.MutArray" are built on top of this
-- module. This module provides two type classes for serialization, 'Unbox' and
-- 'Serialize'. The speed is similar to, and in some cases many times faster
-- than the store package. Conceptually, the 'Serialize' type class works in
-- the same way as store.
--
-- You probably want the higher level
-- 'Streamly.Internal.Data.Array.pinnedSerialize' and
-- 'Streamly.Internal.Data.Array.deserialize' from the "Streamly.Data.Array"
-- module.
--
-- == Mutable Byte Array
--
-- 'MutByteArray' is a primitive mutable array in the IO monad. 'Unbox' and
-- 'Serialize' type classes use this primitive array to serialize data to and
-- deserialize it from. This array can be wrapped into higher level unboxed
-- deserialize it from. This array is used to build higher level unboxed
-- array types 'Streamly.Data.MutArray.MutArray' and 'Streamly.Data.Array.Array'.
--
-- == Using Unbox
@ -38,9 +45,12 @@
-- The 'Serialize' type class is a superset of the 'Unbox' type class, it can
-- serialize variable length data types as well e.g. Haskell lists. Use
-- 'deriveSerialize' to derive the instances of the type class automatically
-- and then use 'pinnedEncode', 'decode' to serialize and deserialize the type
-- to and from an 'Array' type. You can also serialize and deserialize directly
-- to and from a 'MutByteArray', using the type class methods.
-- and then use the type class methods to serialize and deserialize to and from
-- a 'MutByteArray'.
--
-- See 'Streamly.Internal.Data.Array.pinnedSerialize' and
-- 'Streamly.Internal.Data.Array.deserialize' for 'Array' type based
-- serialization.
--
module Streamly.Data.MutByteArray
(
@ -62,7 +72,7 @@ module Streamly.Data.MutByteArray
-- * Serialize
, Serialize(..)
-- Deriving instances
-- Deriving Serialize
, SerializeConfig
, serializeConfig
, inlineSize
@ -71,11 +81,6 @@ module Streamly.Data.MutByteArray
, deriveSerialize
, deriveSerializeWith
-- Encoding and Decoding
-- , encode
, pinnedEncode
, decode
) where
--------------------------------------------------------------------------------

View File

@ -76,13 +76,19 @@ module Streamly.Internal.Data.Array
-- ** Folding
, streamFold
, fold
-- ** Serialization
, encodeAs
, serialize
, pinnedSerialize
, deserialize
)
where
#include "assert.hs"
#include "inline.hs"
#include "ArrayMacros.h"
import Control.Exception (assert)
import Control.Monad (when)
import Control.Monad.IO.Class (MonadIO(..))
import Data.Functor.Identity (Identity)
@ -94,6 +100,8 @@ import Foreign.Storable (Storable)
import Streamly.Internal.Data.Unbox (Unbox(..))
import Prelude hiding (length, null, last, map, (!!), read, concat)
import Streamly.Internal.Data.MutByteArray.Type (PinnedState(..))
import Streamly.Internal.Data.Serialize.Type (Serialize)
import Streamly.Internal.Data.Fold.Type (Fold(..))
import Streamly.Internal.Data.Producer.Type (Producer(..))
import Streamly.Internal.Data.Stream (Stream)
@ -101,7 +109,8 @@ import Streamly.Internal.Data.Tuple.Strict (Tuple3Fused'(..))
import Streamly.Internal.Data.Unfold.Type (Unfold(..))
import Streamly.Internal.System.IO (unsafeInlineIO)
import qualified Streamly.Internal.Data.MutArray.Type as MA
import qualified Streamly.Internal.Data.Serialize.Type as Serialize
import qualified Streamly.Internal.Data.MutByteArray.Type as MBA
import qualified Streamly.Internal.Data.MutArray as MA
import qualified Streamly.Internal.Data.Array.Type as A
import qualified Streamly.Internal.Data.Fold as FL
@ -543,3 +552,38 @@ fold f arr = Stream.fold f (A.read arr)
{-# INLINE streamFold #-}
streamFold :: (Monad m, Unbox a) => (Stream m a -> m b) -> Array a -> m b
streamFold f arr = f (A.read arr)
--------------------------------------------------------------------------------
-- Serialization
--------------------------------------------------------------------------------
{-# INLINE encodeAs #-}
encodeAs :: forall a. Serialize a => PinnedState -> a -> Array Word8
encodeAs ps a =
unsafeInlineIO $ do
let len = Serialize.size 0 a
mbarr <- MBA.newBytesAs ps len
off <- Serialize.serialize 0 mbarr a
assertM(len == off)
pure $ Array mbarr 0 off
{-# INLINE serialize #-}
serialize :: Serialize a => a -> Array Word8
serialize = encodeAs Unpinned
-- | Serialize a Haskell type to a pinned byte array. The array is allocated
-- using pinned memory so that it can be used directly in OS APIs for writing
-- to file or sending over the network.
{-# INLINE pinnedSerialize #-}
pinnedSerialize :: Serialize a => a -> Array Word8
pinnedSerialize = encodeAs Pinned
-- | Decode a Haskell type from a byte array containing its serialized
-- representation.
{-# INLINE deserialize #-}
deserialize :: Serialize a => Array Word8 -> a
deserialize arr@(Array {..}) = unsafeInlineIO $ do
let lenArr = length arr
(off, val) <- Serialize.deserialize arrStart arrContents (arrStart + lenArr)
assertM(off == arrStart + lenArr)
pure val

View File

@ -9,36 +9,24 @@
module Streamly.Internal.Data.Serialize.Type
(
Serialize(..)
, encode
, encodeAs
, pinnedEncode
, decode
) where
--------------------------------------------------------------------------------
-- Imports
--------------------------------------------------------------------------------
#include "assert.hs"
#ifdef DEBUG
import Control.Exception (assert)
#endif
import Data.List (foldl')
import Data.Proxy (Proxy (..))
import Streamly.Internal.Data.Unbox (Unbox)
import Streamly.Internal.Data.MutByteArray.Type
(MutByteArray(..), PinnedState(..))
import Streamly.Internal.Data.MutByteArray.Type (MutByteArray(..))
import Streamly.Internal.Data.Array.Type (Array(..))
import Streamly.Internal.System.IO (unsafeInlineIO)
import GHC.Int (Int16(..), Int32(..), Int64(..), Int8(..))
import GHC.Word (Word16(..), Word32(..), Word64(..), Word8(..))
import GHC.Stable (StablePtr(..))
import qualified Streamly.Internal.Data.MutByteArray.Type as MBA
import qualified Streamly.Internal.Data.Unbox as Unbox
import qualified Streamly.Internal.Data.Array as Array
import qualified Streamly.Internal.Data.Array.Type as Array
import qualified Streamly.Internal.Data.MutArray as MutArray
import GHC.Exts
@ -314,38 +302,3 @@ instance (Serialize a, Serialize b) => Serialize (a, b) where
(off1, a) <- deserialize off arr end
(off2, b) <- deserialize off1 arr end
pure (off2, (a, b))
--------------------------------------------------------------------------------
-- High level functions
--------------------------------------------------------------------------------
{-# INLINE encodeAs #-}
encodeAs :: forall a. Serialize a => PinnedState -> a -> Array Word8
encodeAs ps a =
unsafeInlineIO $ do
let len = size 0 a
mbarr <- MBA.newBytesAs ps len
off <- serialize 0 mbarr a
assertM(len == off)
pure $ Array mbarr 0 off
{-# INLINE encode #-}
encode :: Serialize a => a -> Array Word8
encode = encodeAs Unpinned
-- | Encode a Haskell type to a byte array. The array is allocated using pinned
-- memory so that it can be used directly in OS APIs for writing to file or
-- sending over the network.
{-# INLINE pinnedEncode #-}
pinnedEncode :: Serialize a => a -> Array Word8
pinnedEncode = encodeAs Pinned
-- | Decode a Haskell type from its serialized representation in a byte
-- array.
{-# INLINE decode #-}
decode :: Serialize a => Array Word8 -> a
decode arr@(Array {..}) = unsafeInlineIO $ do
let lenArr = Array.length arr
(off, val) <- deserialize arrStart arrContents (arrStart + lenArr)
assertM(off == arrStart + lenArr)
pure val

View File

@ -185,9 +185,9 @@ peekAndVerify (arr, serStartOff, serEndOff) val = do
val2 `shouldBe` val
off2 `shouldBe` serEndOff
let slice = Array.Array arr serStartOff serEndOff
val `shouldBe` Serialize.decode slice
val `shouldBe` Array.deserialize slice
clonedSlice <- Array.clone slice
val `shouldBe` Serialize.decode clonedSlice
val `shouldBe` Array.deserialize clonedSlice
roundtrip
:: forall a. (Eq a, Show a, Serialize.Serialize a)
@ -195,7 +195,7 @@ roundtrip
-> IO ()
roundtrip val = do
val `shouldBe` Serialize.decode (Serialize.encode val)
val `shouldBe` Array.deserialize (Array.pinnedSerialize val)
res <- poke val
peekAndVerify res val