Abstract out Unboxing helpers and comment out IOVec code

This commit is contained in:
Adithya Kumar 2022-06-15 13:28:15 +05:30
parent ffca3ac5fe
commit adc2e75b5d
26 changed files with 117 additions and 22 deletions

View File

@ -48,7 +48,7 @@ import Streamly.Benchmark.Common
import Streamly.Benchmark.Common.Handle
#ifdef INSPECTION
import Foreign.Storable (Storable)
import Streamly.Internal.Data.Unboxed (Storable)
import Streamly.Internal.Data.Stream.StreamD.Type (Step(..))
import Test.Inspection
#endif

View File

@ -35,7 +35,7 @@ import Streamly.Benchmark.Common
import Streamly.Benchmark.Common.Handle
#ifdef INSPECTION
import Foreign.Storable (Storable)
import Streamly.Internal.Data.Unboxed (Storable)
import Streamly.Internal.Data.Stream.StreamD.Type (Step(..))
import qualified Streamly.Internal.Data.Fold.Type as Fold
import qualified Streamly.Internal.Data.Tuple.Strict as Strict

View File

@ -123,7 +123,7 @@ import Data.Functor.Identity (Identity)
import Data.Word (Word8)
import Foreign.C.String (CString)
import Foreign.Ptr (plusPtr, castPtr)
import Foreign.Storable (Storable(..))
import Streamly.Internal.Data.Unboxed (Storable, peek, sizeOf)
import Prelude hiding (length, null, last, map, (!!), read, concat)
import Streamly.Internal.Data.Array.Foreign.Mut.Type (ReadUState(..), touch)

View File

@ -33,7 +33,7 @@ module Streamly.Internal.Data.Array.Foreign.Mut
where
import Control.Monad.IO.Class (MonadIO(..))
import Foreign.Storable (Storable)
import Streamly.Internal.Data.Unboxed (Storable)
import Streamly.Internal.Data.Stream.Serial (SerialT(..))
import Streamly.Internal.Data.Unfold.Type (Unfold(..))

View File

@ -233,7 +233,9 @@ import Foreign.ForeignPtr.Unsafe (unsafeForeignPtrToPtr)
import Foreign.Marshal.Alloc (mallocBytes)
#endif
import Foreign.Ptr (plusPtr, minusPtr, castPtr, nullPtr)
import Foreign.Storable (Storable(..))
import Streamly.Internal.Data.Unboxed
( Storable, alignment, peek, poke, sizeOf
)
import GHC.Base
( touch#, IO(..), byteArrayContents#
, Int(..), newAlignedPinnedByteArray#

View File

@ -84,7 +84,7 @@ import Data.Word (Word8)
import Foreign.C.String (CString)
import Foreign.C.Types (CSize(..))
import Foreign.Ptr (plusPtr, castPtr)
import Foreign.Storable (Storable(..))
import Streamly.Internal.Data.Unboxed (Storable, peek, sizeOf)
import GHC.Base (Addr#, nullAddr#, build)
import GHC.Exts (IsList, IsString(..))
import GHC.ForeignPtr (ForeignPtr)

View File

@ -61,7 +61,7 @@ import Control.Exception (assert)
import Control.Monad.Catch (MonadThrow)
import Control.Monad.IO.Class (MonadIO(..))
import Foreign.Ptr (minusPtr, plusPtr)
import Foreign.Storable (Storable(..))
import Streamly.Internal.Data.Unboxed (Storable, peek, sizeOf)
import GHC.Types (SPEC(..))
import Streamly.Internal.Data.Array.Foreign.Mut.Type (touch)
import Streamly.Internal.Data.Array.Foreign.Type (Array(..))

View File

@ -31,7 +31,7 @@ import Control.Monad.IO.Class (MonadIO(..))
import Control.Monad (when)
import Control.Monad.Catch (MonadThrow)
import Data.Bifunctor (first)
import Foreign.Storable (Storable(..))
import Streamly.Internal.Data.Unboxed (Storable, sizeOf)
import Streamly.Internal.Data.Array.Foreign.Mut.Type (Array(..))
import Streamly.Internal.Data.Fold.Type (Fold(..))
import Streamly.Internal.Data.Stream.Serial (SerialT(..))

View File

@ -303,7 +303,7 @@ import Data.IORef (newIORef, readIORef, writeIORef)
import Data.Map.Strict (Map)
import Data.Maybe (isJust, fromJust)
import Data.Word (Word32)
import Foreign.Storable (Storable(..))
import Streamly.Internal.Data.Unboxed (Storable, peek, sizeOf)
import Streamly.Internal.Data.IsMap (IsMap(..))
import Streamly.Internal.Data.Pipe.Type (Pipe (..), PipeState(..))
import Streamly.Internal.Data.Unfold.Type (Unfold(..))

View File

@ -53,7 +53,7 @@ where
import Control.Monad.IO.Class (MonadIO (liftIO))
import Data.Bifunctor(bimap)
import Foreign (Storable(..))
import Streamly.Internal.Data.Unboxed (Storable, peek)
import Streamly.Internal.Data.Fold.Type (Fold(..), Step(..))
import Streamly.Internal.Data.Tuple.Strict

View File

@ -78,7 +78,9 @@ import Data.Word (Word8)
import Foreign.ForeignPtr (ForeignPtr, withForeignPtr, touchForeignPtr)
import Foreign.ForeignPtr.Unsafe (unsafeForeignPtrToPtr)
import Foreign.Ptr (plusPtr, minusPtr, castPtr)
import Foreign.Storable (Storable(..))
import Streamly.Internal.Data.Unboxed
( Storable, alignment, peek, poke, sizeOf
)
import GHC.ForeignPtr (mallocPlainForeignPtrAlignedBytes)
import GHC.Ptr (Ptr(..))
import Streamly.Internal.Data.Array.Foreign.Mut.Type (Array, memcmp)

View File

@ -155,7 +155,7 @@ import Control.Monad.IO.Class (MonadIO(..))
import Data.Bits (shiftR, shiftL, (.|.), (.&.))
import Data.Functor.Identity ( Identity )
import Data.Word (Word32)
import Foreign.Storable (Storable(..))
import Streamly.Internal.Data.Unboxed (Storable, peek, sizeOf)
import Fusion.Plugin.Types (Fuse(..))
import GHC.Types (SPEC(..))

View File

@ -0,0 +1,60 @@
{-# OPTIONS_GHC -fno-warn-orphans #-}
{-# LANGUAGE UnboxedTuples #-}
module Streamly.Internal.Data.Unboxed
( Storable
, alignment
, peek
, poke
, sizeOf
) where
#ifdef USE_STORABLE
import Foreign.Storable (Storable(..))
#else
import Data.Int (Int8)
import Data.Primitive.Types (Prim(..), sizeOf, alignment)
import GHC.Base (IO(..))
import GHC.Ptr (Ptr(..))
#endif
#ifndef USE_STORABLE
type Storable = Prim
{-# INLINE peek #-}
peek :: Prim a => Ptr a -> IO a
peek (Ptr addr#) = IO $ \s# -> readOffAddr# addr# 0# s#
{-# INLINE poke #-}
poke :: Prim a => Ptr a -> a -> IO ()
poke (Ptr addr#) a = IO $ \s# -> (# writeOffAddr# addr# 0# a s#, () #)
-- | Orphan Prim instance of Bool implemented using Int8
instance Prim Bool where
sizeOf# _ = sizeOf# (undefined :: Int8)
alignment# _ = alignment# (undefined :: Int8)
indexByteArray# arr# i# = indexByteArray# arr# i# /= (0 :: Int8)
readByteArray# arr# i# s# =
case readByteArray# arr# i# s# of
(# s1#, i :: Int8 #) -> (# s1#, i /= 0 #)
writeByteArray# arr# i# a s# =
case a of
True -> writeByteArray# arr# i# (1 :: Int8) s#
False -> writeByteArray# arr# i# (0 :: Int8) s#
setByteArray# arr# off# len# a s# =
case a of
True -> setByteArray# arr# off# len# (1 :: Int8) s#
False -> setByteArray# arr# off# len# (0 :: Int8) s#
indexOffAddr# addr# i# = indexOffAddr# addr# i# /= (0 :: Int8)
readOffAddr# addr# i# s# =
case readOffAddr# addr# i# s# of
(# s1#, i :: Int8 #) -> (# s1#, i /= 0 #)
writeOffAddr# addr# i# a s# =
case a of
True -> writeOffAddr# addr# i# (1 :: Int8) s#
False -> writeOffAddr# addr# i# (0 :: Int8) s#
setOffAddr# addr# off# len# a s# =
case a of
True -> setOffAddr# addr# off# len# (1 :: Int8) s#
False -> setOffAddr# addr# off# len# (0 :: Int8) s#
#endif

View File

@ -82,6 +82,11 @@ flag use-unliftio
manual: True
default: False
flag use-storable
description: Use Storable for unboxed arrays
manual: True
default: False
-------------------------------------------------------------------------------
-- Common stanzas
-------------------------------------------------------------------------------
@ -101,6 +106,9 @@ common compile-options
if flag(use-c-malloc)
cpp-options: -DUSE_C_MALLOC
if flag(use-storable)
cpp-options: -DUSE_STORABLE
ghc-options: -Wall
-Wcompat
-Wunrecognised-warning-flags
@ -258,6 +266,7 @@ library
, Streamly.Internal.Data.Pipe.Type
-- streamly-core-array-types
, Streamly.Internal.Data.Unboxed
-- Unboxed IORef
-- XXX Depends on primitive
, Streamly.Internal.Data.IORef.Prim

View File

@ -60,7 +60,7 @@ import Data.Semigroup (Semigroup(..))
import Data.Word (Word8)
import Foreign.ForeignPtr (touchForeignPtr)
import Foreign.Ptr (minusPtr, plusPtr, castPtr)
import Foreign.Storable (Storable(..))
import Streamly.Internal.Data.Unboxed (Storable, peek, sizeOf)
import Fusion.Plugin.Types (Fuse(..))
import GHC.Exts (SpecConstrAnnotation(..))
import GHC.ForeignPtr (ForeignPtr(..))

View File

@ -69,7 +69,7 @@ where
import Control.Concurrent (threadDelay)
import Control.Monad.IO.Class (MonadIO(..))
import Foreign.Storable (Storable)
import Streamly.Internal.Data.Unboxed (Storable)
import Streamly.Internal.Control.Concurrent (MonadAsync)
import Streamly.Internal.Data.Array.Foreign.Type (Array)
import Streamly.Internal.Data.Fold.Type (Fold (..))

View File

@ -157,7 +157,7 @@ where
import Control.Monad.Catch (MonadThrow)
import Control.Monad.IO.Class (MonadIO(..))
import Control.Monad.Trans.Class (MonadTrans(..))
import Foreign.Storable (Storable)
import Streamly.Internal.Data.Unboxed (Storable)
import Streamly.Internal.Control.Concurrent (MonadAsync)
import Streamly.Internal.Data.Parser (Parser (..))
import Streamly.Internal.Data.SVar (defState)

View File

@ -157,7 +157,7 @@ import Data.Kind (Type)
import Data.Map (Map)
import Data.Maybe (isNothing)
import Data.Proxy (Proxy(..))
import Foreign.Storable (Storable)
import Streamly.Internal.Data.Unboxed (Storable)
import Streamly.Internal.Control.Concurrent (MonadAsync)
import Streamly.Internal.Data.Fold.Type (Fold (..))
import Streamly.Internal.Data.IsMap (IsMap(..))

View File

@ -121,7 +121,7 @@ import Data.Word (Word8)
import Foreign.ForeignPtr (withForeignPtr)
-- import Foreign.ForeignPtr.Unsafe (unsafeForeignPtrToPtr)
import Foreign.Ptr (plusPtr, castPtr)
import Foreign.Storable (Storable(..))
import Streamly.Internal.Data.Unboxed (Storable)
import GHC.ForeignPtr (mallocPlainForeignPtrBytes)
-- import System.IO (Handle, hGetBufSome, hPutBuf)
import System.IO (IOMode)
@ -138,10 +138,12 @@ import Streamly.Internal.Data.Stream.Serial (SerialT)
import Streamly.Internal.Data.Stream.IsStream.Type
(IsStream, mkStream, fromStreamD)
#if !defined(mingw32_HOST_OS)
{-
import Streamly.Internal.Data.Stream.IsStream.Type (toStreamD)
import Streamly.Internal.System.IOVec (groupIOVecsOf)
import qualified Streamly.Internal.FileSystem.FDIO as RawIO hiding (write)
import qualified Streamly.Internal.System.IOVec.Type as RawIO
-}
#endif
-- import Streamly.Data.Fold (Fold)
-- import Streamly.String (encodeUtf8, decodeUtf8, foldLines)
@ -258,6 +260,7 @@ writeArray (Handle fd) arr =
aLen = byteLength arr
#if !defined(mingw32_HOST_OS)
{-
-- | Write an array of 'IOVec' to a file handle.
--
-- @since 0.7.0
@ -267,6 +270,7 @@ writeIOVec _ iov | A.length iov == 0 = return ()
writeIOVec (Handle fd) iov =
asPtrUnsafe iov $ \p ->
RawIO.writevAll fd p (A.length iov)
-}
#endif
-------------------------------------------------------------------------------
@ -366,6 +370,7 @@ writeArraysPackedUpto :: (MonadIO m, Storable a)
writeArraysPackedUpto n h xs = writeArrays h $ AS.compact n xs
#if !defined(mingw32_HOST_OS)
{-
-- XXX this is incomplete
-- | Write a stream of 'IOVec' arrays to a handle.
--
@ -386,6 +391,7 @@ _writevArraysPackedUpto :: MonadIO m
=> Int -> Handle -> SerialT m (Array a) -> m ()
_writevArraysPackedUpto n h xs =
writev h $ fromStreamD $ groupIOVecsOf n 512 (toStreamD xs)
-}
#endif
-- GHC buffer size dEFAULT_FD_BUFFER_SIZE=8192 bytes.

View File

@ -116,7 +116,7 @@ import Data.Maybe (isNothing, fromJust)
import Data.Word (Word8)
import Foreign.ForeignPtr (withForeignPtr)
import Foreign.Ptr (minusPtr, plusPtr)
import Foreign.Storable (Storable(..))
import Streamly.Internal.Data.Unboxed (Storable)
import GHC.ForeignPtr (mallocPlainForeignPtrBytes)
import System.IO (Handle, SeekMode(..), hGetBufSome, hPutBuf, hSeek)
import Prelude hiding (read)

View File

@ -76,7 +76,7 @@ import Control.Monad (forM_, when)
import Data.Maybe (isNothing, fromJust)
import Data.Word (Word8)
import Foreign.Ptr (minusPtr, plusPtr, Ptr, castPtr)
import Foreign.Storable (Storable(..))
import Streamly.Internal.Data.Unboxed (Storable)
import GHC.ForeignPtr (mallocPlainForeignPtrBytes)
import Network.Socket
(Socket, SocketOption(..), Family(..), SockAddr(..),

View File

@ -15,8 +15,10 @@ module Streamly.Internal.System.IOVec
, c_writev
, c_safe_writev
#if !defined(mingw32_HOST_OS)
{-
, groupIOVecsOf
, groupIOVecsOfMut
-}
#endif
)
where
@ -24,6 +26,7 @@ where
#include "inline.hs"
#if !defined(mingw32_HOST_OS)
{-
import Control.Monad (when)
import Control.Monad.IO.Class (MonadIO(..))
import Foreign.Ptr (castPtr)
@ -34,6 +37,7 @@ import Streamly.Internal.Data.Array.Foreign.Mut.Type (Array(..))
import qualified Streamly.Internal.Data.Array.Foreign.Type as Array
import qualified Streamly.Internal.Data.Array.Foreign.Mut.Type as MArray
import qualified Streamly.Internal.Data.Stream.StreamD as D
-}
#endif
import Streamly.Internal.System.IOVec.Type
@ -41,6 +45,7 @@ import Streamly.Internal.System.IOVec.Type
import Prelude hiding (length)
#if !defined(mingw32_HOST_OS)
{-
data GatherState s arr
= GatherInitial s
| GatherBuffering s arr Int
@ -123,4 +128,5 @@ groupIOVecsOf n maxIOVLen str =
D.map Array.unsafeFreeze
$ groupIOVecsOfMut n maxIOVLen
$ D.map Array.unsafeThaw str
-}
#endif

View File

@ -168,6 +168,7 @@ extra-source-files:
core/src/Streamly/Internal/Data/Parser/ParserK/Type.hs
core/src/Streamly/Internal/Data/Parser/ParserD/Type.hs
core/src/Streamly/Internal/Data/Pipe/Type.hs
core/src/Streamly/Internal/Data/Unboxed.hs
core/src/Streamly/Internal/Data/IORef/Prim.hs
core/src/Streamly/Internal/Data/Array/Foreign/Mut/Type.hs
core/src/Streamly/Internal/Data/Array/Foreign/Mut.hs
@ -300,6 +301,11 @@ flag limit-build-mem
manual: True
default: False
flag use-storable
description: Use Storable for unboxed arrays
manual: True
default: False
-------------------------------------------------------------------------------
-- Common stanzas
-------------------------------------------------------------------------------
@ -328,6 +334,9 @@ common compile-options
if flag(use-c-malloc)
cpp-options: -DUSE_C_MALLOC
if flag(use-storable)
cpp-options: -DUSE_STORABLE
ghc-options: -Wall
-Wcompat
-Wunrecognised-warning-flags
@ -571,6 +580,7 @@ library
, Streamly.Internal.Data.Pipe.Type
-- streamly-core-array-types
, Streamly.Internal.Data.Unboxed
-- Unboxed IORef
-- XXX Depends on primitive
, Streamly.Internal.Data.IORef.Prim

View File

@ -1,5 +1,5 @@
import Foreign.Storable (Storable(..))
import Streamly.Internal.Data.Unboxed (sizeOf)
import Test.Hspec.QuickCheck
import Test.QuickCheck (Property, forAll, Gen, vectorOf, arbitrary, choose)

View File

@ -10,7 +10,7 @@ module Streamly.Test.FileSystem.Handle (main) where
import Data.Functor.Identity (runIdentity)
import Data.Word (Word8)
import Foreign.Storable (Storable(..))
import Streamly.Internal.Data.Unboxed (sizeOf)
import Streamly.Internal.Data.Stream.IsStream (IsStream, SerialT)
import System.FilePath ((</>))
import System.IO

View File

@ -17,7 +17,7 @@ import Data.Int (Int64)
import Data.List (sort, group, intercalate)
import Data.Maybe ( isJust, fromJust )
import Data.Word (Word8)
import Foreign.Storable (Storable)
import Streamly.Internal.Data.Unboxed (Storable)
#if __GLASGOW_HASKELL__ < 808
import Data.Semigroup ((<>))
#endif