diff --git a/benchmark/Streamly/Benchmark/Data/Builder.hs b/benchmark/Streamly/Benchmark/Data/Builder.hs new file mode 100644 index 0000000000..82bef36031 --- /dev/null +++ b/benchmark/Streamly/Benchmark/Data/Builder.hs @@ -0,0 +1,201 @@ +-- | +-- Module : Streamly.Benchmark.Prelude +-- Copyright : (c) 2020 Composewell Technologies +-- +-- License : BSD-3-Clause +-- Maintainer : streamly@composewell.com + +module Main where + +import Streamly.Prelude (SerialT, serially) + +import qualified Streamly.Internal.Data.Stream.IsStream as Stream +import qualified Streamly.Internal.Data.Builder as Builder +import qualified Streamly.Internal.Data.Monoid.Builder as MBuilder + +import Gauge +import Streamly.Benchmark.Common +import Streamly.Benchmark.Prelude + +moduleName :: String +moduleName = "Data.Builder" + +------------------------------------------------------------------------------- +-- Right Associated Appends +------------------------------------------------------------------------------- + +{-# INLINE appendListSourceR #-} +appendListSourceR :: Int -> Int -> [Int] +appendListSourceR value n = + Prelude.foldr (Prelude.++) [] (Prelude.fmap (: []) [n..n+value]) + +{-# INLINE appendListBuilderSourceR #-} +appendListBuilderSourceR :: Int -> Int -> [Int] +appendListBuilderSourceR value n = + Builder.use $ foldMap (Builder.add . (: [])) [n..n+value] + +{-# INLINE consListBuilderSourceR #-} +consListBuilderSourceR :: Int -> Int -> [Int] +consListBuilderSourceR value n = + Builder.use $ foldMap Builder.mk [n..n+value] + +{-# INLINE appendSourceR #-} +appendSourceR :: Int -> Int -> SerialT m Int +appendSourceR value n = foldMap Stream.yield [n..n+value] + +{-# INLINE consStreamBuilderSourceR #-} +consStreamBuilderSourceR :: Int -> Int -> SerialT m Int +consStreamBuilderSourceR value n = + Builder.use $ foldMap Builder.mk [n..n+value] + +{-# INLINE appendStreamBuilderSourceR #-} +appendStreamBuilderSourceR :: Int -> Int -> SerialT m Int +appendStreamBuilderSourceR value n = + Builder.use $ foldMap (Builder.add . Stream.yield) [n..n+value] + +o_1_space_appendR :: Int -> [Benchmark] +o_1_space_appendR value = + [ bgroup "appendR" + [ benchPure "singleton lists" (appendListSourceR value) id + , benchIOSrc serially "singleton streams" (appendSourceR value) + , benchPure "consed list builders" (consListBuilderSourceR value) id + , benchPure + "singleton list builders" (appendListBuilderSourceR value) id + , benchIOSrc + serially + "singleton stream builders" + (appendStreamBuilderSourceR value) + , benchIOSrc + serially + "consed stream builders" + (consStreamBuilderSourceR value) + ] + ] + +------------------------------------------------------------------------------- +-- Left Associated Appends +------------------------------------------------------------------------------- + +{-# INLINE appendListSourceL #-} +appendListSourceL :: Int -> Int -> [Int] +appendListSourceL value n = + Prelude.foldl (Prelude.++) [] (map (: []) [n..n+value]) + +{-# INLINE appendListBuilderSourceL #-} +appendListBuilderSourceL :: Int -> Int -> [Int] +appendListBuilderSourceL value n = + Builder.use + $ Prelude.foldl + (<>) mempty (map (Builder.add . (: [])) [n..n+value]) + +{-# INLINE appendListMonoidBuilderSourceL #-} +appendListMonoidBuilderSourceL :: Int -> Int -> [Int] +appendListMonoidBuilderSourceL value n = + MBuilder.use + $ Prelude.foldl (<>) mempty (map (MBuilder.mk . (: [])) [n..n+value]) + +{-# INLINE consListBuilderSourceL #-} +consListBuilderSourceL :: Int -> Int -> [Int] +consListBuilderSourceL value n = + Builder.use + $ Prelude.foldl (<>) mempty (map Builder.mk [n..n+value]) + +{-# INLINE appendSourceL #-} +appendSourceL :: Int -> Int -> SerialT m Int +appendSourceL value n = + Prelude.foldl + (Prelude.<>) Stream.nil (Prelude.fmap Stream.yield [n..n+value]) + +{-# INLINE appendStreamBuilderSourceL #-} +appendStreamBuilderSourceL :: Int -> Int -> SerialT m Int +appendStreamBuilderSourceL value n = + Builder.use + $ Prelude.foldl + (<>) + mempty + (map (Builder.add . Stream.yield) [n..n+value]) + +{-# INLINE consStreamBuilderSourceL #-} +consStreamBuilderSourceL :: Int -> Int -> SerialT m Int +consStreamBuilderSourceL value n = + Builder.use + $ Prelude.foldl (<>) mempty (map Builder.mk [n..n+value]) + +{-# INLINE appendStreamMonoidBuilderSourceL #-} +appendStreamMonoidBuilderSourceL :: Int -> Int -> SerialT m Int +appendStreamMonoidBuilderSourceL value n = + MBuilder.use + $ Prelude.foldl + (<>) mempty (map (MBuilder.mk . Stream.yield) [n..n+value]) + +-- Use builder of streams and concat +{-# INLINE streamConcatStreamBuilderSourceL #-} +streamConcatStreamBuilderSourceL :: Monad m => Int -> Int -> SerialT m Int +streamConcatStreamBuilderSourceL value n = + Stream.concat + $ Builder.use + $ Prelude.foldl + (<>) + mempty + (map (Builder.mk . Stream.yield) [n..n+value]) + +o_1_space_appendL :: Int -> [Benchmark] +o_1_space_appendL value = + [ bgroup "appendL" + [ benchPure + "singleton lists (n/100)" (appendListSourceL (value `div` 100)) id + , benchPure + "singleton list builders" + (appendListBuilderSourceL value) + id + , benchPure + "singleton list monoid builders" + (appendListMonoidBuilderSourceL value) + id + , benchPure + "consed list builders" + (consListBuilderSourceL value) + id + , benchIOSrc + serially + "singleton streams (n/100)" + (appendSourceL (value `div` 100)) + , benchIOSrc + serially + "singleton stream builders" + (appendStreamBuilderSourceL value) + , benchIOSrc + serially + "consed stream builders" + (consStreamBuilderSourceL value) + , benchIOSrc + serially + "singleton stream monoid builders" + (appendStreamMonoidBuilderSourceL value) + , benchIOSrc + serially + "Stream.concat stream builders" + (streamConcatStreamBuilderSourceL value) + ] + ] + +------------------------------------------------------------------------------- +-- Main +------------------------------------------------------------------------------- + +-- In addition to gauge options, the number of elements in the stream can be +-- passed using the --stream-size option. +-- +main :: IO () +main = do + (value, cfg, benches) <- parseCLIOpts defaultStreamSize + value `seq` runMode (mode cfg) cfg benches (allBenchmarks value) + + where + + allBenchmarks size = + [ bgroup (o_1_space_prefix moduleName) $ Prelude.concat + [ o_1_space_appendR size + , o_1_space_appendL size + ] + ] diff --git a/benchmark/Streamly/Benchmark/Prelude/Serial.hs b/benchmark/Streamly/Benchmark/Prelude/Serial.hs index e65a986375..d0c0eb6ed5 100644 --- a/benchmark/Streamly/Benchmark/Prelude/Serial.hs +++ b/benchmark/Streamly/Benchmark/Prelude/Serial.hs @@ -1470,13 +1470,13 @@ o_1_space_joining value = o_1_space_concatFoldable :: Int -> [Benchmark] o_1_space_concatFoldable value = [ bgroup "concat-foldable" - [ benchIOSrc serially "foldMapWith (<>) (List)" + [ benchIOSrc serially "concatMapFoldableWith (<>) yield (List)" (sourceFoldMapWith value) - , benchIOSrc serially "foldMapWith (<>) (Stream)" + , benchIOSrc serially "concatMapFoldableWith (<>) yield (Stream)" (sourceFoldMapWithStream value) - , benchIOSrc serially "foldMapWithM (<>) (List)" + , benchIOSrc serially "concatMapFoldableWith (<>) yieldM (List)" (sourceFoldMapWithM value) - , benchIOSrc serially "foldMapM (List)" (sourceFoldMapM value) + , benchIOSrc serially "foldMap yieldM (List)" (sourceFoldMapM value) ] ] diff --git a/benchmark/streamly-benchmarks.cabal b/benchmark/streamly-benchmarks.cabal index 4e210b328e..975ded8b52 100644 --- a/benchmark/streamly-benchmarks.cabal +++ b/benchmark/streamly-benchmarks.cabal @@ -300,6 +300,16 @@ benchmark Data.Parser buildable: True build-depends: exceptions >= 0.8 && < 0.11 +benchmark Data.Builder + import: bench-options + type: exitcode-stdio-1.0 + hs-source-dirs: Streamly/Benchmark/Data + main-is: Builder.hs + if impl(ghcjs) + buildable: False + else + buildable: True + ------------------------------------------------------------------------------- -- Raw Streams ------------------------------------------------------------------------------- diff --git a/src/Streamly/Internal/Data/Builder.hs b/src/Streamly/Internal/Data/Builder.hs new file mode 100644 index 0000000000..e025062586 --- /dev/null +++ b/src/Streamly/Internal/Data/Builder.hs @@ -0,0 +1,352 @@ +-- | +-- Module : Streamly.Internal.Data.Builder +-- Copyright : (c) 2020 Composewell Technologies +-- License : BSD-3-Clause +-- Maintainer : streamly@composewell.com +-- Stability : experimental +-- Portability : GHC +-- +-- Building a right associative structure by incremental appending. +-- +-- = Right Associative Structures +-- +-- Right associative consable structures (Haskell lists or streamly streams) +-- can be extended on the left maintaining O(1) lazy consumption +-- characteristics, however, they do not provide a @snoc@ operation to extend on +-- the right. The semigroup operation ('<>') can be used for appends. However, +-- from performance standpoint (<>) is a right associative operation, when left +-- associated, which is the case for incremental appends, each append adds one +-- nesting layer making the lazy consumption to take O(n^2), @n@ being the +-- number of appends. +-- +-- = Illustration +-- +-- The following expressions build a list in a natural right associated manner: +-- +-- @ +-- a : b : c ... : [] +-- a <> b <> c <> ... +-- a <> (b <> (c <> ...)) +-- @ +-- +-- However, consider incremental appending in a program: +-- +-- @ +-- let x = a <> b +-- y = x <> c +-- z = y <> ... +-- @ +-- +-- The expression @z@ would be equivalent to: +-- +-- @ +-- z = ((a <> b) <> c) <> ... +-- @ +-- +-- This is a left associated append which would make the consumption to take +-- O(n^2) where @n@ is the number of appends. +-- +-- = Associative Builders +-- +-- Builders are truly associative monoidal containers which can be extended on +-- the left as well as right side while maintaining an O(1) lazy consumption +-- characteristics. Left associative or right associative appending does not +-- make any difference. However, an uncons like operation on builders would +-- require O(n) time. +-- +-- The idea is to use right associative representations for lazy +-- transformations (requiring uncons) and fully associative representations for +-- incremental appending (requiring snoc). A builder must be converted to a +-- right associated structure if we want to transform it. For that reason, it +-- does not make sense for a builder to represent an infinite structure. +-- Therefore, builders are used to build finite right associative structures by +-- incremental appending. +-- +-- = Usage +-- +-- == Using cons and snoc operators +-- +-- Build using elements: +-- +-- >>> b1 = 'h' <+ 'i' <+ mempty -- Builder t Char +-- >>> b2 = b1 +> '!' -- Builder t Char +-- >>> use b2 :: [Char] +-- "hi!" +-- >>> use b2 :: SerialT Identity Char +-- "hi!" +-- +-- Build using containers: +-- +-- >>> b1 = "hello" <++ " world" <++ mempty -- Builder [] Char +-- >>> b2 = b1 ++> "!!" -- Builder [] Char +-- >>> use b2 -- [Char] +-- "hello world!!" +-- +-- Mixed: +-- +-- >>> b1 = 'h' <+ "ello" <++ mempty -- Builder [] Char +-- >>> b2 = b1 ++> " world" +> '!' -- Builder [] Char +-- >>> use b2 -- [Char] +-- "hello world!" +-- +-- == Using 'cons' and 'snoc' +-- +-- >>> b1 = 'h' `cons` "ello" `bcons` mempty -- Builder [] Char +-- >>> b2 = b1 `bsnoc` " world" `snoc` '!' -- Builder [] Char +-- >>> use b2 -- [Char] +-- "hello world!" +-- +-- == Using 'mk', 'add' and ('<>') +-- +-- >>> b1 = mk 'h' <> add "ello" -- Builder [] Char +-- >>> b2 = b1 <> add " world" <> mk '!' -- Builder [] Char +-- >>> use b2 -- [Char] +-- "hello world!" +-- +-- = Notes +-- +-- In general, we should preclude the possibility of left associated appends +-- because that is just inefficient. Is it possible to use static analysis to +-- find out all such uses in existing code? + +module Streamly.Internal.Data.Builder + ( Builder (..) + , Buildable (..) + + -- * Construction + , nil + + , cons + , snoc + , (<+) + , (+>) + + , bcons + , bsnoc + , (<++) + , (++>) + + -- * Experimental + + -- ** Generation + -- | Experimental. In general, we can generate a structure and lift it into + -- a builder. For lists there is no perf difference in wrapping lists in a + -- builder vs wrapping elements. In case of streams there is a 2x + -- difference in worst case of singleton streams, however, in practical use + -- cases it may not matter. + , unfoldr -- experimental, use builder + + , append -- use (<>) + + -- ** Conversion + , fromFoldable -- experimental, use foldMap mk + + -- ** Elimination + , final + ) +where + +import Data.Semigroup (Semigroup (..)) +import Streamly.Internal.Data.Stream.Serial (SerialT) +import qualified Streamly.Internal.Data.Stream.StreamK as Serial + +import Prelude hiding (concat) + +-- A builder represents a 'Consable' container. It is essentially a linked list +-- of functions (continuations), each function generating a part of the +-- container. The builder in this module is essentially difference lists +-- generalized to a 'Consable'. This is fully associative builder. +newtype Builder t a = Builder (t a -> t a) + +class Buildable t where + -- | Make a builder from a single element. + mk :: a -> Builder t a + -- | Make a builder from a container. + add :: t a -> Builder t a + -- | Use the builder as the underlying container type. + use :: Builder t a -> t a + +instance Buildable [] where + mk = Builder . (:) + add = Builder . (++) + use (Builder k) = k [] + +instance Buildable (SerialT m) where + mk = Builder . (Serial.cons) + add = Builder . (Serial.serial) + use (Builder k) = k Serial.nil + +------------------------------------------------------------------------------- +-- Construction +------------------------------------------------------------------------------- + +-- | Append two builders sequentially, the left or right associativity of the +-- expression does not matter, @(a `append` b) `append` c@ has the same +-- performance characterstics as @a `append` (b `append` c)@. +-- +-- /Internal/ +-- +{-# INLINE append #-} +append :: Builder t a -> Builder t a -> Builder t a +append (Builder k1) (Builder k2) = Builder $ \next -> k1 (k2 next) + +instance Semigroup (Builder t a) where + {-# INLINE (<>) #-} + (<>) = append + + {-# INLINE stimes #-} + stimes n x + | n < 0 = error "Streamly.Data.Builder.stimes: negative multiplier" + | otherwise = times n + + where + + times 0 = nil + times i = x <> times (pred i) + +-- | An empty builder. +-- +-- > nil = Builder id +-- +-- /Internal/ +-- +nil :: Builder t a +nil = Builder id + +instance Monoid (Builder t a) where + mempty = nil + +infixr 5 `cons` + +-- | Add a value at the head of the builder. Right associvative when used +-- infix. +-- +-- > cons a b = mk a <> b +-- +-- /Internal/ +-- +cons :: Buildable t => a -> Builder t a -> Builder t a +cons a b = mk a <> b + +infixr 5 <+ + +-- | Same as 'cons'. Right associvative. +-- +-- /Internal/ +-- +(<+) :: Buildable t => a -> Builder t a -> Builder t a +(<+) = cons + +-- +-- | Add a value at the tail of the builder. Left associvative when used infix. +-- +-- > snoc b a = b <> mk a +-- +-- /Internal/ +-- +snoc :: Buildable t => Builder t a -> a -> Builder t a +snoc b a = b <> mk a + +-- | Same as 'snoc'. Left associvative. +-- +-- /Internal/ +-- +(+>) :: Buildable t => Builder t a -> a -> Builder t a +(+>) = snoc + +------------------------------------------------------------------------------- +-- Semigroup operations +------------------------------------------------------------------------------- + +infixr 5 `bcons` + +-- | Extend a builder by prepending a structure at the beginning. Right +-- associvative when used infix. +-- +-- > bcons xs b = add xs <> b +-- +-- /Internal/ +-- +bcons :: Buildable t => t a -> Builder t a -> Builder t a +bcons xs b = add xs <> b + +infixr 5 <++ + +-- | Same as 'bcons'. Right associative. +-- +-- /Internal/ +-- +(<++) :: Buildable t => t a -> Builder t a -> Builder t a +(<++) = bcons + +-- | Extend a builder by appending a structure at the end. Left associative +-- when used infix. +-- +-- > bsnoc b xs = b <> add xs +-- +-- /Internal/ +-- +bsnoc :: Buildable t => Builder t a -> t a -> Builder t a +bsnoc b xs = b <> add xs + +-- | Same as 'bsnoc'. Left associative. +-- +-- /Internal/ +-- +(++>) :: Buildable t => Builder t a -> t a -> Builder t a +(++>) = bsnoc + +------------------------------------------------------------------------------- +-- Generation +------------------------------------------------------------------------------- + +-- Directly generate sequences into a builder instead of reconstructing a +-- builder from another container. +-- +-- XXX add other operations like repeat/replicate etc. + +-- | Unfold a seed generating a builder. +-- +-- /Internal/ +-- +unfoldr :: Buildable t => (b -> Maybe (a, b)) -> b -> Builder t a +unfoldr step b = + case step b of + Nothing -> nil + Just (a, b1) -> mk a <> unfoldr step b1 + +------------------------------------------------------------------------------- +-- Conversion +------------------------------------------------------------------------------- +-- +-- | Convert a 'Foldable' container to a builder. +-- +-- > fromFoldable = foldMap mk +-- +-- /Internal/ +-- +fromFoldable :: (Foldable t1, Buildable t2) => t1 a -> Builder t2 a +fromFoldable = foldMap mk + +------------------------------------------------------------------------------- +-- Elimination +------------------------------------------------------------------------------- + +-- | Close a builder by appending a final container to it. +-- +-- This is experimental. We can always 'extendR' and 'use instead. +-- +-- /Internal/ +-- +{-# INLINE final #-} +final :: Builder t a -> t a -> t a +final (Builder k) = k + +{- +-- XXX creates an intermediate structure, can it be fused? +-- The foldable instance essentially realizes the builder to underlying +-- container and folds it. For simplicity, it is perhaps better to perform +-- operations on the container explicitly rather doing it on the builder. +instance (Buildable t, Foldable t) => Foldable (Builder t) where + foldMap f = foldMap f . use +-} diff --git a/src/Streamly/Internal/Data/Consable.hs b/src/Streamly/Internal/Data/Consable.hs new file mode 100644 index 0000000000..f9bf343dfa --- /dev/null +++ b/src/Streamly/Internal/Data/Consable.hs @@ -0,0 +1,40 @@ +-- | +-- Module : Streamly.Internal.Data.Consable +-- Copyright : (c) 2020 Composewell Technologies +-- License : BSD-3-Clause +-- Maintainer : streamly@composewell.com +-- Stability : experimental +-- Portability : GHC + +module Streamly.Internal.Data.Consable + ( Consable (..) + ) +where + +import Streamly.Internal.Data.Stream.Serial (SerialT) +import qualified Streamly.Internal.Data.Stream.StreamK as Serial +import Prelude hiding (map) + +------------------------------------------------------------------------------- +-- Construction +------------------------------------------------------------------------------- + +infixr 5 `cons` + +-- Originally to unify some operations (builder) on lists and streams. +-- +-- | Pure list like structures that can be constructed using "cons" and "nil". +class Consable t where + -- | An empty value. + nil :: t a + -- | A right associative cons operation. + cons :: a -> t a -> t a + +instance Consable [] where + nil = [] + cons = (:) + +-- XXX should move to Stream.Serial? +instance Consable (SerialT m) where + nil = Serial.nil + cons = Serial.cons diff --git a/src/Streamly/Internal/Data/Monoid/Builder.hs b/src/Streamly/Internal/Data/Monoid/Builder.hs new file mode 100644 index 0000000000..4521586ca5 --- /dev/null +++ b/src/Streamly/Internal/Data/Monoid/Builder.hs @@ -0,0 +1,145 @@ +-- | +-- Module : Streamly.Internal.Data.Monoid.Builder +-- Copyright : (c) 2020 Composewell Technologies +-- License : BSD-3-Clause +-- Maintainer : streamly@composewell.com +-- Stability : experimental +-- Portability : GHC +-- +-- This is basically 'Endo' for a Monoid type with a builder interface. We +-- can use this for building strings or lists or any other monoid type. This +-- performs as well as a as a difference list. +-- +-- = Usage +-- +-- >>> b1 = mk "hello " +-- >>> b2 = b1 <> mk "world!" +-- >>> use b2 +-- "hello world!" +-- +module Streamly.Internal.Data.Monoid.Builder + ( Builder (..) + + -- * Construction + , mk + + -- * Elimination + , use + + -- * Experimental + , nil -- use mempty + , cons + , snoc + , fromFoldable -- use foldMap mk + , final + ) +where + +import Data.Semigroup (Semigroup (..)) +import Prelude hiding (concat) + +newtype Builder a = Builder (a -> a) + +------------------------------------------------------------------------------- +-- Construction +------------------------------------------------------------------------------- + +-- | Lift a single element to a builder. +-- +-- /Internal/ +-- +mk :: Monoid a => a -> Builder a +mk = Builder . (<>) + +-- | Append two builders sequentially, the left or right associativity of the +-- expression does not matter, @(a `append` b) `append` c@ has the same +-- performance characterstics as @a `append` (b `append` c)@. +-- +-- /Internal/ +-- +{-# INLINE append #-} +append :: Builder a -> Builder a -> Builder a +append (Builder k1) (Builder k2) = Builder $ \next -> k1 (k2 next) + +instance Semigroup (Builder a) where + {-# INLINE (<>) #-} + (<>) = append + + {-# INLINE stimes #-} + stimes n x + | n < 0 = error "Streamly.Data.Builder.stimes: negative multiplier" + | otherwise = times n + + where + + times 0 = nil + times i = x <> times (pred i) + +-- | An empty builder. +-- +-- > nil = Builder id +-- +-- /Internal/ +-- +nil :: Builder a +nil = Builder id + +instance Monoid (Builder a) where + mempty = nil + +infixr 5 `cons` + +-- (.>) +-- +-- | Add a value at the head of the builder. +-- +-- > cons a b = mk a <> b +-- +-- /Internal/ +-- +cons :: Monoid a => a -> Builder a -> Builder a +cons a b = mk a <> b + +-- (<.) +-- +-- | Add a value at the tail of the builder. +-- +-- > snoc b a = b <> mk a +-- +-- /Internal/ +-- +snoc :: Monoid a => Builder a -> a -> Builder a +snoc b a = b <> mk a + +------------------------------------------------------------------------------- +-- Conversion +------------------------------------------------------------------------------- +-- +-- | Convert a 'Foldable' container to a builder. +-- +-- > fromFoldable = foldMap mk +-- +-- /Internal/ +-- +fromFoldable :: (Foldable t, Monoid a) => t a -> Builder a +fromFoldable = foldMap mk + +------------------------------------------------------------------------------- +-- Elimination +------------------------------------------------------------------------------- + +-- | Close the builder and extract the container. +-- +-- /Internal/ +-- +{-# INLINE use #-} +use :: Monoid a => Builder a -> a +use (Builder k) = k mempty + +-- | Close a builder by appending a final value to it. +-- +-- /Internal/ +-- +{-# INLINE final #-} +final :: Builder a -> a -> a +final (Builder k) = k diff --git a/streamly.cabal b/streamly.cabal index d4fb2c4083..ec632ec8e4 100644 --- a/streamly.cabal +++ b/streamly.cabal @@ -412,6 +412,9 @@ library , Streamly.Internal.Data.Time.Units , Streamly.Internal.Data.Time.Clock , Streamly.Internal.Data.SVar + , Streamly.Internal.Data.Monoid.Builder + , Streamly.Internal.Data.Builder + , Streamly.Internal.Data.Consable -- Memory storage , Streamly.Internal.Foreign.Malloc