From 1be4cb1204694c006ac34693a15061b3a2cb2460 Mon Sep 17 00:00:00 2001 From: Harendra Kumar Date: Thu, 24 Sep 2020 17:37:35 +0530 Subject: [PATCH 1/9] Rename foldWith/foldMapWith etc. As per the renaming in Prelude. --- benchmark/Streamly/Benchmark/Prelude/Serial.hs | 8 ++++---- 1 file changed, 4 insertions(+), 4 deletions(-) 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) ] ] From c29e522b1ea7de1bbbcf159545a5f16db8287a12 Mon Sep 17 00:00:00 2001 From: Harendra Kumar Date: Sun, 17 May 2020 16:49:14 +0530 Subject: [PATCH 2/9] Add builder data type --- benchmark/Streamly/Benchmark/Data/Builder.hs | 192 +++++++++++++ benchmark/streamly-benchmarks.cabal | 10 + src/Streamly/Internal/Data/Builder.hs | 286 +++++++++++++++++++ src/Streamly/Internal/Data/Consable.hs | 40 +++ streamly.cabal | 2 + 5 files changed, 530 insertions(+) create mode 100644 benchmark/Streamly/Benchmark/Data/Builder.hs create mode 100644 src/Streamly/Internal/Data/Builder.hs create mode 100644 src/Streamly/Internal/Data/Consable.hs diff --git a/benchmark/Streamly/Benchmark/Data/Builder.hs b/benchmark/Streamly/Benchmark/Data/Builder.hs new file mode 100644 index 0000000000..fcf518ffef --- /dev/null +++ b/benchmark/Streamly/Benchmark/Data/Builder.hs @@ -0,0 +1,192 @@ +-- | +-- Module : Streamly.Benchmark.Prelude +-- Copyright : (c) 2020 Composewell Technologies +-- +-- License : BSD-3-Clause +-- Maintainer : streamly@composewell.com + +module Main where + +import Data.Functor.Identity (Identity) +import Streamly.Prelude (SerialT, serially) + +import qualified Streamly.Internal.Data.Stream.IsStream as Stream +import qualified Streamly.Internal.Data.Builder as Builder + +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.close $ foldMap (Builder.build . (: [])) [n..n+value] + +{-# INLINE consListBuilderSourceR #-} +consListBuilderSourceR :: Int -> Int -> [Int] +consListBuilderSourceR value n = + Builder.close $ foldMap Builder.solo [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.close $ foldMap Builder.solo [n..n+value] + +{-# INLINE appendStreamBuilderSourceR #-} +appendStreamBuilderSourceR :: Int -> Int -> SerialT m Int +appendStreamBuilderSourceR value n = + Builder.close $ foldMap (Builder.build . 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.++) [] (Prelude.map (: []) [n..n+value]) + +{-# INLINE appendListBuilderSourceL #-} +appendListBuilderSourceL :: Int -> Int -> [Int] +appendListBuilderSourceL value n = + Builder.close + $ Prelude.foldl + (<>) mempty (Prelude.map (Builder.build . (: [])) [n..n+value]) + +{-# INLINE consListBuilderSourceL #-} +consListBuilderSourceL :: Int -> Int -> [Int] +consListBuilderSourceL value n = + Builder.close + $ Prelude.foldl (<>) mempty (Prelude.map Builder.solo [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.close + $ Prelude.foldl + (<>) + mempty + (Prelude.map (Builder.build . Stream.yield) [n..n+value]) + +{-# INLINE consStreamBuilderSourceL #-} +consStreamBuilderSourceL :: Int -> Int -> SerialT m Int +consStreamBuilderSourceL value n = + Builder.close + $ Prelude.foldl (<>) mempty (Prelude.map Builder.solo [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.close + $ Prelude.foldl + (<>) + mempty + (Prelude.map (Builder.solo . Stream.yield) [n..n+value]) + +{-# INLINE builderConcatStreamBuilderSourceL #-} +builderConcatStreamBuilderSourceL :: Int -> Int -> SerialT Identity Int +builderConcatStreamBuilderSourceL value n = + Builder.concat + $ Prelude.foldl + (<>) + mempty + (Prelude.map (Builder.solo . (Stream.yield :: Int -> SerialT Identity Int)) [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 + "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 + "Stream.concat stream builders" + (streamConcatStreamBuilderSourceL value) + , benchPureSrc + "Builder.concat stream builders" + (builderConcatStreamBuilderSourceL 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-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..7ba513e46e --- /dev/null +++ b/src/Streamly/Internal/Data/Builder.hs @@ -0,0 +1,286 @@ +-- | +-- 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). +-- +-- = 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. +-- +-- = 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 (..) + + -- * Construction + , nil + , solo + , cons + , snoc + + -- * 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 + + -- * Semigroup + -- | Open a 'Consable' structure for O(1) appends irrespective of + -- associativity. We can then cheaply extend it on the left or on the + -- right. + + , append -- use (<>) + , build + , extendL -- cons + , extendR -- snoc + + -- * Conversion + , fromFoldable -- experimental, use foldMap solo + + -- * Elimination + , close + , final + , concat -- this is of limited use perhaps + ) +where + +import Data.Semigroup (Semigroup (..)) +import Streamly.Internal.Data.Consable (Consable) + +import qualified Streamly.Internal.Data.Consable as Consable + +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) + +------------------------------------------------------------------------------- +-- Construction +------------------------------------------------------------------------------- + +-- | Lift a singleton value to a builder. +-- +-- For streams this is 2x faster than using 'build' with singleton streams. +-- +-- /Internal/ +-- +solo :: Consable t => a -> Builder t a +solo = Builder . Consable.cons + +-- | 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 + +-- | Add a value at the head of the builder. +-- +-- > cons a b = solo a <> b +-- +-- /Internal/ +-- +cons :: Consable t => a -> Builder t a -> Builder t a +cons a b = solo a <> b + +-- | Add a value at the tail of the builder. +-- +-- > snoc b a = b <> solo a +-- +-- /Internal/ +-- +snoc :: Consable t => Builder t a -> a -> Builder t a +snoc b a = b <> solo a + +------------------------------------------------------------------------------- +-- Semigroup operations +------------------------------------------------------------------------------- + +-- | Wrap a 'Semigroup' capable container into a builder. +-- +-- > build = Builder . (<>) +-- +-- /Internal/ +-- +build :: Semigroup (t a) => t a -> Builder t a +build = Builder . (<>) + +-- | Extend a builder by appending a structure on the right side. +-- +-- > extendR b xs = b <> build xs +-- +-- /Internal/ +-- +extendR :: Semigroup (t a) => Builder t a -> t a -> Builder t a +extendR b xs = b <> build xs + +-- | Extend a builder by prepending a structure on the left side. +-- +-- > extendL xs b = build xs <> b +-- +-- /Internal/ +-- +extendL :: Semigroup (t a) => t a -> Builder t a -> Builder t a +extendL xs b = build xs <> b + +------------------------------------------------------------------------------- +-- 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 :: Consable t => (b -> Maybe (a, b)) -> b -> Builder t a +unfoldr step b = + case step b of + Nothing -> nil + Just (a, b1) -> a `cons` unfoldr step b1 + +------------------------------------------------------------------------------- +-- Conversion +------------------------------------------------------------------------------- +-- +-- | Convert a 'Foldable' container to a builder. +-- +-- > fromFoldable = foldMap solo +-- +-- /Internal/ +-- +fromFoldable :: (Foldable t1, Consable t2) => t1 a -> Builder t2 a +fromFoldable = foldMap solo + +------------------------------------------------------------------------------- +-- Elimination +------------------------------------------------------------------------------- + +-- | Close the builder and extract the container. +-- +-- /Internal/ +-- +{-# INLINE close #-} +close :: Consable t => Builder t a -> t a +close (Builder k) = k Consable.nil + +-- | Close a builder by appending a final container to it. +-- +-- This is experimental. We can always 'extendR' and 'close' instead. +-- +-- /Internal/ +-- +{-# INLINE final #-} +final :: Builder t a -> t a -> t a +final (Builder k) = k + +-- | Flatten a builder building a container of containers. +-- +-- /Internal/ +-- +concat :: (Consable t1, Foldable t1, Foldable t2) => Builder t1 (t2 a) -> t1 a +concat = foldr (\x y -> foldr Consable.cons y x) Consable.nil . close + +{- +-- 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 (Consable t, Foldable t) => Foldable (Builder t) where + foldMap f = foldMap f . close +-} 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/streamly.cabal b/streamly.cabal index d4fb2c4083..86b5011297 100644 --- a/streamly.cabal +++ b/streamly.cabal @@ -412,6 +412,8 @@ library , Streamly.Internal.Data.Time.Units , Streamly.Internal.Data.Time.Clock , Streamly.Internal.Data.SVar + , Streamly.Internal.Data.Builder + , Streamly.Internal.Data.Consable -- Memory storage , Streamly.Internal.Foreign.Malloc From 64905fef38ad1e099a914650fd6257c4c23d05b7 Mon Sep 17 00:00:00 2001 From: Harendra Kumar Date: Thu, 24 Sep 2020 23:11:38 +0530 Subject: [PATCH 3/9] fixup: change names, add doc --- benchmark/Streamly/Benchmark/Data/Builder.hs | 20 ++-- src/Streamly/Internal/Data/Builder.hs | 113 ++++++++++++++----- 2 files changed, 96 insertions(+), 37 deletions(-) diff --git a/benchmark/Streamly/Benchmark/Data/Builder.hs b/benchmark/Streamly/Benchmark/Data/Builder.hs index fcf518ffef..105e8a4694 100644 --- a/benchmark/Streamly/Benchmark/Data/Builder.hs +++ b/benchmark/Streamly/Benchmark/Data/Builder.hs @@ -32,12 +32,12 @@ appendListSourceR value n = {-# INLINE appendListBuilderSourceR #-} appendListBuilderSourceR :: Int -> Int -> [Int] appendListBuilderSourceR value n = - Builder.close $ foldMap (Builder.build . (: [])) [n..n+value] + Builder.close $ foldMap (Builder.bag . (: [])) [n..n+value] {-# INLINE consListBuilderSourceR #-} consListBuilderSourceR :: Int -> Int -> [Int] consListBuilderSourceR value n = - Builder.close $ foldMap Builder.solo [n..n+value] + Builder.close $ foldMap Builder.one [n..n+value] {-# INLINE appendSourceR #-} appendSourceR :: Int -> Int -> SerialT m Int @@ -46,12 +46,12 @@ appendSourceR value n = foldMap Stream.yield [n..n+value] {-# INLINE consStreamBuilderSourceR #-} consStreamBuilderSourceR :: Int -> Int -> SerialT m Int consStreamBuilderSourceR value n = - Builder.close $ foldMap Builder.solo [n..n+value] + Builder.close $ foldMap Builder.one [n..n+value] {-# INLINE appendStreamBuilderSourceR #-} appendStreamBuilderSourceR :: Int -> Int -> SerialT m Int appendStreamBuilderSourceR value n = - Builder.close $ foldMap (Builder.build . Stream.yield) [n..n+value] + Builder.close $ foldMap (Builder.bag . Stream.yield) [n..n+value] o_1_space_appendR :: Int -> [Benchmark] o_1_space_appendR value = @@ -86,13 +86,13 @@ appendListBuilderSourceL :: Int -> Int -> [Int] appendListBuilderSourceL value n = Builder.close $ Prelude.foldl - (<>) mempty (Prelude.map (Builder.build . (: [])) [n..n+value]) + (<>) mempty (Prelude.map (Builder.bag . (: [])) [n..n+value]) {-# INLINE consListBuilderSourceL #-} consListBuilderSourceL :: Int -> Int -> [Int] consListBuilderSourceL value n = Builder.close - $ Prelude.foldl (<>) mempty (Prelude.map Builder.solo [n..n+value]) + $ Prelude.foldl (<>) mempty (Prelude.map Builder.one [n..n+value]) {-# INLINE appendSourceL #-} appendSourceL :: Int -> Int -> SerialT m Int @@ -107,13 +107,13 @@ appendStreamBuilderSourceL value n = $ Prelude.foldl (<>) mempty - (Prelude.map (Builder.build . Stream.yield) [n..n+value]) + (Prelude.map (Builder.bag . Stream.yield) [n..n+value]) {-# INLINE consStreamBuilderSourceL #-} consStreamBuilderSourceL :: Int -> Int -> SerialT m Int consStreamBuilderSourceL value n = Builder.close - $ Prelude.foldl (<>) mempty (Prelude.map Builder.solo [n..n+value]) + $ Prelude.foldl (<>) mempty (Prelude.map Builder.one [n..n+value]) -- Use builder of streams and concat {-# INLINE streamConcatStreamBuilderSourceL #-} @@ -124,7 +124,7 @@ streamConcatStreamBuilderSourceL value n = $ Prelude.foldl (<>) mempty - (Prelude.map (Builder.solo . Stream.yield) [n..n+value]) + (Prelude.map (Builder.one . Stream.yield) [n..n+value]) {-# INLINE builderConcatStreamBuilderSourceL #-} builderConcatStreamBuilderSourceL :: Int -> Int -> SerialT Identity Int @@ -133,7 +133,7 @@ builderConcatStreamBuilderSourceL value n = $ Prelude.foldl (<>) mempty - (Prelude.map (Builder.solo . (Stream.yield :: Int -> SerialT Identity Int)) [n..n+value]) + (Prelude.map (Builder.one . (Stream.yield :: Int -> SerialT Identity Int)) [n..n+value]) o_1_space_appendL :: Int -> [Benchmark] o_1_space_appendL value = diff --git a/src/Streamly/Internal/Data/Builder.hs b/src/Streamly/Internal/Data/Builder.hs index 7ba513e46e..3e925a5215 100644 --- a/src/Streamly/Internal/Data/Builder.hs +++ b/src/Streamly/Internal/Data/Builder.hs @@ -16,7 +16,8 @@ -- 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). +-- nesting layer making the lazy consumption to take O(n^2), @n@ being the +-- number of appends. -- -- = Illustration -- @@ -61,6 +62,52 @@ -- Therefore, builders are used to build finite right associative structures by -- incremental appending. -- +-- = Usage +-- +-- == Using 'one', 'bag' and ('<>') +-- +-- Using '<>': +-- +-- @ +-- one x <> one y :: 'Builder' [] a +-- one x <> one y & 'close' :: [a] +-- @ +-- +-- @ +-- bag xs <> bag ys :: 'Builder' [] a +-- bag xs <> bag ys & 'close' :: [a] +-- @ +-- +-- == Using 'cons', 'snoc' and 'nil' +-- +-- Right associative, building with elements: +-- +-- @ +-- x `'cons'` y `'cons'` 'nil' :: 'Builder' [] a +-- 'close' $ x `'cons'` y `'cons'` 'nil' :: [a] +-- @ +-- +-- Right associative, building with lists: +-- +-- @ +-- xs `'bcons'` ys `'bcons'` 'nil' :: 'Builder' [] a +-- 'close' $ xs `'bcons'` ys `'bcons'` 'nil' :: [a] +-- @ +-- +-- Left associative, building with elements: +-- +-- @ +-- 'nil' `'snoc'` x `'snoc'` y :: 'Builder' [] a +-- 'nil' `'snoc'` x `'snoc'` y & 'close' :: [a] +-- @ +-- +-- Left associative, building with lists: +-- +-- @ +-- 'nil' `'bsnoc'` x `'bsnoc'` y :: 'Builder' [] a +-- 'nil' `'bsnoc'` x `'bsnoc'` y & 'close' :: [a] +-- @ +-- -- = Notes -- -- In general, we should preclude the possibility of left associated appends @@ -72,7 +119,7 @@ module Streamly.Internal.Data.Builder -- * Construction , nil - , solo + , one , cons , snoc @@ -90,12 +137,12 @@ module Streamly.Internal.Data.Builder -- right. , append -- use (<>) - , build - , extendL -- cons - , extendR -- snoc + , bag + , bcons + , bsnoc -- * Conversion - , fromFoldable -- experimental, use foldMap solo + , fromFoldable -- experimental, use foldMap one -- * Elimination , close @@ -121,14 +168,14 @@ newtype Builder t a = Builder (t a -> t a) -- Construction ------------------------------------------------------------------------------- --- | Lift a singleton value to a builder. +-- | Lift a single element to a builder. -- -- For streams this is 2x faster than using 'build' with singleton streams. -- -- /Internal/ -- -solo :: Consable t => a -> Builder t a -solo = Builder . Consable.cons +one :: Consable t => a -> Builder t a +one = Builder . Consable.cons -- | Append two builders sequentially, the left or right associativity of the -- expression does not matter, @(a `append` b) `append` c@ has the same @@ -166,54 +213,66 @@ nil = Builder id instance Monoid (Builder t a) where mempty = nil +infixr 5 `cons` + +-- (.>) +-- -- | Add a value at the head of the builder. -- --- > cons a b = solo a <> b +-- > cons a b = one a <> b -- -- /Internal/ -- cons :: Consable t => a -> Builder t a -> Builder t a -cons a b = solo a <> b +cons a b = one a <> b +-- (<.) +-- -- | Add a value at the tail of the builder. -- --- > snoc b a = b <> solo a +-- > snoc b a = b <> one a -- -- /Internal/ -- snoc :: Consable t => Builder t a -> a -> Builder t a -snoc b a = b <> solo a +snoc b a = b <> one a ------------------------------------------------------------------------------- -- Semigroup operations ------------------------------------------------------------------------------- --- | Wrap a 'Semigroup' capable container into a builder. +-- | Lift a 'Semigroup' capable container to a builder. -- --- > build = Builder . (<>) +-- > bag = Builder . (<>) -- -- /Internal/ -- -build :: Semigroup (t a) => t a -> Builder t a -build = Builder . (<>) +bag :: Semigroup (t a) => t a -> Builder t a +bag = Builder . (<>) + +infixr 5 `bcons` --- | Extend a builder by appending a structure on the right side. +-- (+>) -- --- > extendR b xs = b <> build xs +-- | Extend a builder by prepending a structure at the beginning. +-- +-- > bcons xs b = bag xs <> b -- -- /Internal/ -- -extendR :: Semigroup (t a) => Builder t a -> t a -> Builder t a -extendR b xs = b <> build xs +bcons :: Semigroup (t a) => t a -> Builder t a -> Builder t a +bcons xs b = bag xs <> b --- | Extend a builder by prepending a structure on the left side. +-- (<+) +-- +-- | Extend a builder by appending a structure at the end. -- --- > extendL xs b = build xs <> b +-- > bsnoc b xs = b <> bag xs -- -- /Internal/ -- -extendL :: Semigroup (t a) => t a -> Builder t a -> Builder t a -extendL xs b = build xs <> b +bsnoc :: Semigroup (t a) => Builder t a -> t a -> Builder t a +bsnoc b xs = b <> bag xs ------------------------------------------------------------------------------- -- Generation @@ -240,12 +299,12 @@ unfoldr step b = -- -- | Convert a 'Foldable' container to a builder. -- --- > fromFoldable = foldMap solo +-- > fromFoldable = foldMap one -- -- /Internal/ -- fromFoldable :: (Foldable t1, Consable t2) => t1 a -> Builder t2 a -fromFoldable = foldMap solo +fromFoldable = foldMap one ------------------------------------------------------------------------------- -- Elimination From ff68118b905b06573515c8f614fe6e03a2a4328a Mon Sep 17 00:00:00 2001 From: Harendra Kumar Date: Fri, 25 Sep 2020 01:49:06 +0530 Subject: [PATCH 4/9] Add Monoid based builder --- src/Streamly/Internal/Data/Monoid/Builder.hs | 145 +++++++++++++++++++ streamly.cabal | 1 + 2 files changed, 146 insertions(+) create mode 100644 src/Streamly/Internal/Data/Monoid/Builder.hs diff --git a/src/Streamly/Internal/Data/Monoid/Builder.hs b/src/Streamly/Internal/Data/Monoid/Builder.hs new file mode 100644 index 0000000000..265a2120be --- /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 = add "hello " +-- >>> b2 = b1 <> add "world!" +-- >>> close b2 +-- "hello world!" +-- +module Streamly.Internal.Data.Monoid.Builder + ( Builder (..) + + -- * Construction + , add + + -- * Elimination + , close + + -- * Experimental + , nil -- use mempty + , cons + , snoc + , fromFoldable -- use foldMap add + , 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/ +-- +add :: Monoid a => a -> Builder a +add = 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 = add a <> b +-- +-- /Internal/ +-- +cons :: Monoid a => a -> Builder a -> Builder a +cons a b = add a <> b + +-- (<.) +-- +-- | Add a value at the tail of the builder. +-- +-- > snoc b a = b <> add a +-- +-- /Internal/ +-- +snoc :: Monoid a => Builder a -> a -> Builder a +snoc b a = b <> add a + +------------------------------------------------------------------------------- +-- Conversion +------------------------------------------------------------------------------- +-- +-- | Convert a 'Foldable' container to a builder. +-- +-- > fromFoldable = foldMap add +-- +-- /Internal/ +-- +fromFoldable :: (Foldable t, Monoid a) => t a -> Builder a +fromFoldable = foldMap add + +------------------------------------------------------------------------------- +-- Elimination +------------------------------------------------------------------------------- + +-- | Close the builder and extract the container. +-- +-- /Internal/ +-- +{-# INLINE close #-} +close :: Monoid a => Builder a -> a +close (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 86b5011297..ec632ec8e4 100644 --- a/streamly.cabal +++ b/streamly.cabal @@ -412,6 +412,7 @@ 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 From de35e4692124d2d85d9f4a9eeb6cdf506e9a4ae5 Mon Sep 17 00:00:00 2001 From: Harendra Kumar Date: Fri, 25 Sep 2020 01:50:59 +0530 Subject: [PATCH 5/9] Rename one->add, update docs, add benchmark Add benchmark for Monoid builder --- benchmark/Streamly/Benchmark/Data/Builder.hs | 29 +++++-- src/Streamly/Internal/Data/Builder.hs | 91 +++++++------------- 2 files changed, 51 insertions(+), 69 deletions(-) diff --git a/benchmark/Streamly/Benchmark/Data/Builder.hs b/benchmark/Streamly/Benchmark/Data/Builder.hs index 105e8a4694..ac7befee57 100644 --- a/benchmark/Streamly/Benchmark/Data/Builder.hs +++ b/benchmark/Streamly/Benchmark/Data/Builder.hs @@ -12,6 +12,7 @@ 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 @@ -37,7 +38,7 @@ appendListBuilderSourceR value n = {-# INLINE consListBuilderSourceR #-} consListBuilderSourceR :: Int -> Int -> [Int] consListBuilderSourceR value n = - Builder.close $ foldMap Builder.one [n..n+value] + Builder.close $ foldMap Builder.add [n..n+value] {-# INLINE appendSourceR #-} appendSourceR :: Int -> Int -> SerialT m Int @@ -46,7 +47,7 @@ appendSourceR value n = foldMap Stream.yield [n..n+value] {-# INLINE consStreamBuilderSourceR #-} consStreamBuilderSourceR :: Int -> Int -> SerialT m Int consStreamBuilderSourceR value n = - Builder.close $ foldMap Builder.one [n..n+value] + Builder.close $ foldMap Builder.add [n..n+value] {-# INLINE appendStreamBuilderSourceR #-} appendStreamBuilderSourceR :: Int -> Int -> SerialT m Int @@ -79,20 +80,26 @@ o_1_space_appendR value = {-# INLINE appendListSourceL #-} appendListSourceL :: Int -> Int -> [Int] appendListSourceL value n = - Prelude.foldl (Prelude.++) [] (Prelude.map (: []) [n..n+value]) + Prelude.foldl (Prelude.++) [] (map (: []) [n..n+value]) {-# INLINE appendListBuilderSourceL #-} appendListBuilderSourceL :: Int -> Int -> [Int] appendListBuilderSourceL value n = Builder.close $ Prelude.foldl - (<>) mempty (Prelude.map (Builder.bag . (: [])) [n..n+value]) + (<>) mempty (map (Builder.bag . (: [])) [n..n+value]) + +{-# INLINE appendListMonoidBuilderSourceL #-} +appendListMonoidBuilderSourceL :: Int -> Int -> [Int] +appendListMonoidBuilderSourceL value n = + MBuilder.close + $ Prelude.foldl (<>) mempty (map (MBuilder.add . (: [])) [n..n+value]) {-# INLINE consListBuilderSourceL #-} consListBuilderSourceL :: Int -> Int -> [Int] consListBuilderSourceL value n = Builder.close - $ Prelude.foldl (<>) mempty (Prelude.map Builder.one [n..n+value]) + $ Prelude.foldl (<>) mempty (map Builder.add [n..n+value]) {-# INLINE appendSourceL #-} appendSourceL :: Int -> Int -> SerialT m Int @@ -107,13 +114,13 @@ appendStreamBuilderSourceL value n = $ Prelude.foldl (<>) mempty - (Prelude.map (Builder.bag . Stream.yield) [n..n+value]) + (map (Builder.bag . Stream.yield) [n..n+value]) {-# INLINE consStreamBuilderSourceL #-} consStreamBuilderSourceL :: Int -> Int -> SerialT m Int consStreamBuilderSourceL value n = Builder.close - $ Prelude.foldl (<>) mempty (Prelude.map Builder.one [n..n+value]) + $ Prelude.foldl (<>) mempty (map Builder.add [n..n+value]) -- Use builder of streams and concat {-# INLINE streamConcatStreamBuilderSourceL #-} @@ -124,7 +131,7 @@ streamConcatStreamBuilderSourceL value n = $ Prelude.foldl (<>) mempty - (Prelude.map (Builder.one . Stream.yield) [n..n+value]) + (map (Builder.add . Stream.yield) [n..n+value]) {-# INLINE builderConcatStreamBuilderSourceL #-} builderConcatStreamBuilderSourceL :: Int -> Int -> SerialT Identity Int @@ -133,7 +140,7 @@ builderConcatStreamBuilderSourceL value n = $ Prelude.foldl (<>) mempty - (Prelude.map (Builder.one . (Stream.yield :: Int -> SerialT Identity Int)) [n..n+value]) + (map (Builder.add . (Stream.yield :: Int -> SerialT Identity Int)) [n..n+value]) o_1_space_appendL :: Int -> [Benchmark] o_1_space_appendL value = @@ -144,6 +151,10 @@ o_1_space_appendL value = "singleton list builders" (appendListBuilderSourceL value) id + , benchPure + "singleton list monoid builders" + (appendListMonoidBuilderSourceL value) + id , benchPure "consed list builders" (consListBuilderSourceL value) diff --git a/src/Streamly/Internal/Data/Builder.hs b/src/Streamly/Internal/Data/Builder.hs index 3e925a5215..e048d21e3e 100644 --- a/src/Streamly/Internal/Data/Builder.hs +++ b/src/Streamly/Internal/Data/Builder.hs @@ -64,49 +64,21 @@ -- -- = Usage -- --- == Using 'one', 'bag' and ('<>') +-- == Using 'add', 'bag' and ('<>') -- --- Using '<>': +-- >>> b1 = add 'h' -- Builder [] Char +-- >>> b2 = b1 <> add 'e' -- Builder [] Char +-- >>> b3 = b2 <> bag "llo!" -- Builder [] Char +-- >>> close b3 -- [Char] +-- "hello!" -- --- @ --- one x <> one y :: 'Builder' [] a --- one x <> one y & 'close' :: [a] --- @ --- --- @ --- bag xs <> bag ys :: 'Builder' [] a --- bag xs <> bag ys & 'close' :: [a] --- @ --- --- == Using 'cons', 'snoc' and 'nil' --- --- Right associative, building with elements: --- --- @ --- x `'cons'` y `'cons'` 'nil' :: 'Builder' [] a --- 'close' $ x `'cons'` y `'cons'` 'nil' :: [a] --- @ --- --- Right associative, building with lists: --- --- @ --- xs `'bcons'` ys `'bcons'` 'nil' :: 'Builder' [] a --- 'close' $ xs `'bcons'` ys `'bcons'` 'nil' :: [a] --- @ --- --- Left associative, building with elements: +-- == Using 'cons' and 'snoc' -- --- @ --- 'nil' `'snoc'` x `'snoc'` y :: 'Builder' [] a --- 'nil' `'snoc'` x `'snoc'` y & 'close' :: [a] --- @ --- --- Left associative, building with lists: --- --- @ --- 'nil' `'bsnoc'` x `'bsnoc'` y :: 'Builder' [] a --- 'nil' `'bsnoc'` x `'bsnoc'` y & 'close' :: [a] --- @ +-- >>> b1 = 'h' `cons` "el" `bcons` mempty -- Builder [] Char +-- >>> b2 = b1 `snoc` 'l' `snoc` 'o' -- Builder [] Char +-- >>> b3 = b2 `bsnoc` " world!" -- Builder [] Char +-- >>> close b3 -- [Char] +-- "hello world!" -- -- = Notes -- @@ -118,12 +90,18 @@ module Streamly.Internal.Data.Builder ( Builder (..) -- * Construction + , add + , bag + + -- * Elimination + , close + + -- * Experimental , nil - , one , cons , snoc - -- * Generation + -- ** 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 @@ -131,21 +109,14 @@ module Streamly.Internal.Data.Builder -- cases it may not matter. , unfoldr -- experimental, use builder - -- * Semigroup - -- | Open a 'Consable' structure for O(1) appends irrespective of - -- associativity. We can then cheaply extend it on the left or on the - -- right. - , append -- use (<>) - , bag , bcons , bsnoc - -- * Conversion - , fromFoldable -- experimental, use foldMap one + -- ** Conversion + , fromFoldable -- experimental, use foldMap add - -- * Elimination - , close + -- ** Elimination , final , concat -- this is of limited use perhaps ) @@ -174,8 +145,8 @@ newtype Builder t a = Builder (t a -> t a) -- -- /Internal/ -- -one :: Consable t => a -> Builder t a -one = Builder . Consable.cons +add :: Consable t => a -> Builder t a +add = Builder . Consable.cons -- | Append two builders sequentially, the left or right associativity of the -- expression does not matter, @(a `append` b) `append` c@ has the same @@ -219,23 +190,23 @@ infixr 5 `cons` -- -- | Add a value at the head of the builder. -- --- > cons a b = one a <> b +-- > cons a b = add a <> b -- -- /Internal/ -- cons :: Consable t => a -> Builder t a -> Builder t a -cons a b = one a <> b +cons a b = add a <> b -- (<.) -- -- | Add a value at the tail of the builder. -- --- > snoc b a = b <> one a +-- > snoc b a = b <> add a -- -- /Internal/ -- snoc :: Consable t => Builder t a -> a -> Builder t a -snoc b a = b <> one a +snoc b a = b <> add a ------------------------------------------------------------------------------- -- Semigroup operations @@ -299,12 +270,12 @@ unfoldr step b = -- -- | Convert a 'Foldable' container to a builder. -- --- > fromFoldable = foldMap one +-- > fromFoldable = foldMap add -- -- /Internal/ -- fromFoldable :: (Foldable t1, Consable t2) => t1 a -> Builder t2 a -fromFoldable = foldMap one +fromFoldable = foldMap add ------------------------------------------------------------------------------- -- Elimination From a75e7ae683550c82502752bbcd3e288d480abf4f Mon Sep 17 00:00:00 2001 From: Harendra Kumar Date: Fri, 25 Sep 2020 15:37:48 +0530 Subject: [PATCH 6/9] Add Monoid builder benchmark for streams --- benchmark/Streamly/Benchmark/Data/Builder.hs | 11 +++++++++++ 1 file changed, 11 insertions(+) diff --git a/benchmark/Streamly/Benchmark/Data/Builder.hs b/benchmark/Streamly/Benchmark/Data/Builder.hs index ac7befee57..61dab423dc 100644 --- a/benchmark/Streamly/Benchmark/Data/Builder.hs +++ b/benchmark/Streamly/Benchmark/Data/Builder.hs @@ -122,6 +122,13 @@ consStreamBuilderSourceL value n = Builder.close $ Prelude.foldl (<>) mempty (map Builder.add [n..n+value]) +{-# INLINE appendStreamMonoidBuilderSourceL #-} +appendStreamMonoidBuilderSourceL :: Int -> Int -> SerialT m Int +appendStreamMonoidBuilderSourceL value n = + MBuilder.close + $ Prelude.foldl + (<>) mempty (map (MBuilder.add . Stream.yield) [n..n+value]) + -- Use builder of streams and concat {-# INLINE streamConcatStreamBuilderSourceL #-} streamConcatStreamBuilderSourceL :: Monad m => Int -> Int -> SerialT m Int @@ -171,6 +178,10 @@ o_1_space_appendL value = serially "consed stream builders" (consStreamBuilderSourceL value) + , benchIOSrc + serially + "singleton stream monoid builders" + (appendStreamMonoidBuilderSourceL value) , benchIOSrc serially "Stream.concat stream builders" From f7d83ae8ef182b5a1567c86ac4322a9f96cd78aa Mon Sep 17 00:00:00 2001 From: Harendra Kumar Date: Fri, 25 Sep 2020 17:06:16 +0530 Subject: [PATCH 7/9] Rename add/close, add operators --- benchmark/Streamly/Benchmark/Data/Builder.hs | 34 +++---- src/Streamly/Internal/Data/Builder.hs | 93 ++++++++++++++------ src/Streamly/Internal/Data/Monoid/Builder.hs | 34 +++---- 3 files changed, 98 insertions(+), 63 deletions(-) diff --git a/benchmark/Streamly/Benchmark/Data/Builder.hs b/benchmark/Streamly/Benchmark/Data/Builder.hs index 61dab423dc..f5ecfc57e8 100644 --- a/benchmark/Streamly/Benchmark/Data/Builder.hs +++ b/benchmark/Streamly/Benchmark/Data/Builder.hs @@ -33,12 +33,12 @@ appendListSourceR value n = {-# INLINE appendListBuilderSourceR #-} appendListBuilderSourceR :: Int -> Int -> [Int] appendListBuilderSourceR value n = - Builder.close $ foldMap (Builder.bag . (: [])) [n..n+value] + Builder.use $ foldMap (Builder.bag . (: [])) [n..n+value] {-# INLINE consListBuilderSourceR #-} consListBuilderSourceR :: Int -> Int -> [Int] consListBuilderSourceR value n = - Builder.close $ foldMap Builder.add [n..n+value] + Builder.use $ foldMap Builder.mk [n..n+value] {-# INLINE appendSourceR #-} appendSourceR :: Int -> Int -> SerialT m Int @@ -47,12 +47,12 @@ appendSourceR value n = foldMap Stream.yield [n..n+value] {-# INLINE consStreamBuilderSourceR #-} consStreamBuilderSourceR :: Int -> Int -> SerialT m Int consStreamBuilderSourceR value n = - Builder.close $ foldMap Builder.add [n..n+value] + Builder.use $ foldMap Builder.mk [n..n+value] {-# INLINE appendStreamBuilderSourceR #-} appendStreamBuilderSourceR :: Int -> Int -> SerialT m Int appendStreamBuilderSourceR value n = - Builder.close $ foldMap (Builder.bag . Stream.yield) [n..n+value] + Builder.use $ foldMap (Builder.bag . Stream.yield) [n..n+value] o_1_space_appendR :: Int -> [Benchmark] o_1_space_appendR value = @@ -85,21 +85,21 @@ appendListSourceL value n = {-# INLINE appendListBuilderSourceL #-} appendListBuilderSourceL :: Int -> Int -> [Int] appendListBuilderSourceL value n = - Builder.close + Builder.use $ Prelude.foldl (<>) mempty (map (Builder.bag . (: [])) [n..n+value]) {-# INLINE appendListMonoidBuilderSourceL #-} appendListMonoidBuilderSourceL :: Int -> Int -> [Int] appendListMonoidBuilderSourceL value n = - MBuilder.close - $ Prelude.foldl (<>) mempty (map (MBuilder.add . (: [])) [n..n+value]) + MBuilder.use + $ Prelude.foldl (<>) mempty (map (MBuilder.mk . (: [])) [n..n+value]) {-# INLINE consListBuilderSourceL #-} consListBuilderSourceL :: Int -> Int -> [Int] consListBuilderSourceL value n = - Builder.close - $ Prelude.foldl (<>) mempty (map Builder.add [n..n+value]) + Builder.use + $ Prelude.foldl (<>) mempty (map Builder.mk [n..n+value]) {-# INLINE appendSourceL #-} appendSourceL :: Int -> Int -> SerialT m Int @@ -110,7 +110,7 @@ appendSourceL value n = {-# INLINE appendStreamBuilderSourceL #-} appendStreamBuilderSourceL :: Int -> Int -> SerialT m Int appendStreamBuilderSourceL value n = - Builder.close + Builder.use $ Prelude.foldl (<>) mempty @@ -119,26 +119,26 @@ appendStreamBuilderSourceL value n = {-# INLINE consStreamBuilderSourceL #-} consStreamBuilderSourceL :: Int -> Int -> SerialT m Int consStreamBuilderSourceL value n = - Builder.close - $ Prelude.foldl (<>) mempty (map Builder.add [n..n+value]) + Builder.use + $ Prelude.foldl (<>) mempty (map Builder.mk [n..n+value]) {-# INLINE appendStreamMonoidBuilderSourceL #-} appendStreamMonoidBuilderSourceL :: Int -> Int -> SerialT m Int appendStreamMonoidBuilderSourceL value n = - MBuilder.close + MBuilder.use $ Prelude.foldl - (<>) mempty (map (MBuilder.add . Stream.yield) [n..n+value]) + (<>) 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.close + $ Builder.use $ Prelude.foldl (<>) mempty - (map (Builder.add . Stream.yield) [n..n+value]) + (map (Builder.mk . Stream.yield) [n..n+value]) {-# INLINE builderConcatStreamBuilderSourceL #-} builderConcatStreamBuilderSourceL :: Int -> Int -> SerialT Identity Int @@ -147,7 +147,7 @@ builderConcatStreamBuilderSourceL value n = $ Prelude.foldl (<>) mempty - (map (Builder.add . (Stream.yield :: Int -> SerialT Identity Int)) [n..n+value]) + (map (Builder.mk . (Stream.yield :: Int -> SerialT Identity Int)) [n..n+value]) o_1_space_appendL :: Int -> [Benchmark] o_1_space_appendL value = diff --git a/src/Streamly/Internal/Data/Builder.hs b/src/Streamly/Internal/Data/Builder.hs index e048d21e3e..d1f2baef8e 100644 --- a/src/Streamly/Internal/Data/Builder.hs +++ b/src/Streamly/Internal/Data/Builder.hs @@ -64,12 +64,12 @@ -- -- = Usage -- --- == Using 'add', 'bag' and ('<>') +-- == Using 'mk', 'bag' and ('<>') -- --- >>> b1 = add 'h' -- Builder [] Char --- >>> b2 = b1 <> add 'e' -- Builder [] Char --- >>> b3 = b2 <> bag "llo!" -- Builder [] Char --- >>> close b3 -- [Char] +-- >>> b1 = mk 'h' -- Builder [] Char +-- >>> b2 = b1 <> mk 'e' -- Builder [] Char +-- >>> b3 = b2 <> bag "llo!" -- Builder [] Char +-- >>> use b3 -- [Char] -- "hello!" -- -- == Using 'cons' and 'snoc' @@ -77,7 +77,15 @@ -- >>> b1 = 'h' `cons` "el" `bcons` mempty -- Builder [] Char -- >>> b2 = b1 `snoc` 'l' `snoc` 'o' -- Builder [] Char -- >>> b3 = b2 `bsnoc` " world!" -- Builder [] Char --- >>> close b3 -- [Char] +-- >>> use b3 -- [Char] +-- "hello world!" +-- +-- == Using cons and snoc operators +-- +-- >>> b1 = 'h' <+ "el" <++ mempty -- Builder [] Char +-- >>> b2 = b1 +> 'l' +> 'o' -- Builder [] Char +-- >>> b3 = b2 ++> " world!" -- Builder [] Char +-- >>> use b3 -- [Char] -- "hello world!" -- -- = Notes @@ -90,16 +98,18 @@ module Streamly.Internal.Data.Builder ( Builder (..) -- * Construction - , add + , mk , bag -- * Elimination - , close + , use -- * Experimental , nil , cons , snoc + , (<+) + , (+>) -- ** Generation -- | Experimental. In general, we can generate a structure and lift it into @@ -112,9 +122,11 @@ module Streamly.Internal.Data.Builder , append -- use (<>) , bcons , bsnoc + , (<++) + , (++>) -- ** Conversion - , fromFoldable -- experimental, use foldMap add + , fromFoldable -- experimental, use foldMap mk -- ** Elimination , final @@ -145,8 +157,8 @@ newtype Builder t a = Builder (t a -> t a) -- -- /Internal/ -- -add :: Consable t => a -> Builder t a -add = Builder . Consable.cons +mk :: Consable t => a -> Builder t a +mk = Builder . Consable.cons -- | Append two builders sequentially, the left or right associativity of the -- expression does not matter, @(a `append` b) `append` c@ has the same @@ -186,27 +198,38 @@ instance Monoid (Builder t a) where infixr 5 `cons` --- (.>) --- -- | Add a value at the head of the builder. -- --- > cons a b = add a <> b +-- > cons a b = mk a <> b -- -- /Internal/ -- cons :: Consable t => a -> Builder t a -> Builder t a -cons a b = add a <> b +cons a b = mk a <> b + +-- | Same as 'cons'. +-- +-- /Internal/ +-- +(<+) :: Consable t => a -> Builder t a -> Builder t a +(<+) = cons --- (<.) -- -- | Add a value at the tail of the builder. -- --- > snoc b a = b <> add a +-- > snoc b a = b <> mk a -- -- /Internal/ -- snoc :: Consable t => Builder t a -> a -> Builder t a -snoc b a = b <> add a +snoc b a = b <> mk a + +-- | Same as 'snoc'. +-- +-- /Internal/ +-- +(+>) :: Consable t => Builder t a -> a -> Builder t a +(+>) = snoc ------------------------------------------------------------------------------- -- Semigroup operations @@ -223,8 +246,6 @@ bag = Builder . (<>) infixr 5 `bcons` --- (+>) --- -- | Extend a builder by prepending a structure at the beginning. -- -- > bcons xs b = bag xs <> b @@ -234,7 +255,14 @@ infixr 5 `bcons` bcons :: Semigroup (t a) => t a -> Builder t a -> Builder t a bcons xs b = bag xs <> b --- (<+) +-- | Same as 'bcons'. +-- +-- /Internal/ +-- +(<++) :: Semigroup (t a) => t a -> Builder t a -> Builder t a +(<++) = bcons + +-- (++>) -- -- | Extend a builder by appending a structure at the end. -- @@ -245,6 +273,13 @@ bcons xs b = bag xs <> b bsnoc :: Semigroup (t a) => Builder t a -> t a -> Builder t a bsnoc b xs = b <> bag xs +-- | Same as 'bsnoc'. +-- +-- /Internal/ +-- +(++>) :: Semigroup (t a) => Builder t a -> t a -> Builder t a +(++>) = bsnoc + ------------------------------------------------------------------------------- -- Generation ------------------------------------------------------------------------------- @@ -270,12 +305,12 @@ unfoldr step b = -- -- | Convert a 'Foldable' container to a builder. -- --- > fromFoldable = foldMap add +-- > fromFoldable = foldMap mk -- -- /Internal/ -- fromFoldable :: (Foldable t1, Consable t2) => t1 a -> Builder t2 a -fromFoldable = foldMap add +fromFoldable = foldMap mk ------------------------------------------------------------------------------- -- Elimination @@ -285,13 +320,13 @@ fromFoldable = foldMap add -- -- /Internal/ -- -{-# INLINE close #-} -close :: Consable t => Builder t a -> t a -close (Builder k) = k Consable.nil +{-# INLINE use #-} +use :: Consable t => Builder t a -> t a +use (Builder k) = k Consable.nil -- | Close a builder by appending a final container to it. -- --- This is experimental. We can always 'extendR' and 'close' instead. +-- This is experimental. We can always 'extendR' and 'use instead. -- -- /Internal/ -- @@ -304,7 +339,7 @@ final (Builder k) = k -- /Internal/ -- concat :: (Consable t1, Foldable t1, Foldable t2) => Builder t1 (t2 a) -> t1 a -concat = foldr (\x y -> foldr Consable.cons y x) Consable.nil . close +concat = foldr (\x y -> foldr Consable.cons y x) Consable.nil . use {- -- XXX creates an intermediate structure, can it be fused? @@ -312,5 +347,5 @@ concat = foldr (\x y -> foldr Consable.cons y x) Consable.nil . close -- container and folds it. For simplicity, it is perhaps better to perform -- operations on the container explicitly rather doing it on the builder. instance (Consable t, Foldable t) => Foldable (Builder t) where - foldMap f = foldMap f . close + foldMap f = foldMap f . use -} diff --git a/src/Streamly/Internal/Data/Monoid/Builder.hs b/src/Streamly/Internal/Data/Monoid/Builder.hs index 265a2120be..4521586ca5 100644 --- a/src/Streamly/Internal/Data/Monoid/Builder.hs +++ b/src/Streamly/Internal/Data/Monoid/Builder.hs @@ -12,25 +12,25 @@ -- -- = Usage -- --- >>> b1 = add "hello " --- >>> b2 = b1 <> add "world!" --- >>> close b2 +-- >>> b1 = mk "hello " +-- >>> b2 = b1 <> mk "world!" +-- >>> use b2 -- "hello world!" -- module Streamly.Internal.Data.Monoid.Builder ( Builder (..) -- * Construction - , add + , mk -- * Elimination - , close + , use -- * Experimental , nil -- use mempty , cons , snoc - , fromFoldable -- use foldMap add + , fromFoldable -- use foldMap mk , final ) where @@ -48,8 +48,8 @@ newtype Builder a = Builder (a -> a) -- -- /Internal/ -- -add :: Monoid a => a -> Builder a -add = Builder . (<>) +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 @@ -93,23 +93,23 @@ infixr 5 `cons` -- -- | Add a value at the head of the builder. -- --- > cons a b = add a <> b +-- > cons a b = mk a <> b -- -- /Internal/ -- cons :: Monoid a => a -> Builder a -> Builder a -cons a b = add a <> b +cons a b = mk a <> b -- (<.) -- -- | Add a value at the tail of the builder. -- --- > snoc b a = b <> add a +-- > snoc b a = b <> mk a -- -- /Internal/ -- snoc :: Monoid a => Builder a -> a -> Builder a -snoc b a = b <> add a +snoc b a = b <> mk a ------------------------------------------------------------------------------- -- Conversion @@ -117,12 +117,12 @@ snoc b a = b <> add a -- -- | Convert a 'Foldable' container to a builder. -- --- > fromFoldable = foldMap add +-- > fromFoldable = foldMap mk -- -- /Internal/ -- fromFoldable :: (Foldable t, Monoid a) => t a -> Builder a -fromFoldable = foldMap add +fromFoldable = foldMap mk ------------------------------------------------------------------------------- -- Elimination @@ -132,9 +132,9 @@ fromFoldable = foldMap add -- -- /Internal/ -- -{-# INLINE close #-} -close :: Monoid a => Builder a -> a -close (Builder k) = k mempty +{-# INLINE use #-} +use :: Monoid a => Builder a -> a +use (Builder k) = k mempty -- | Close a builder by appending a final value to it. -- From 5d6a889df73c8e1835ec42da1cd1afbed86c674b Mon Sep 17 00:00:00 2001 From: Harendra Kumar Date: Fri, 25 Sep 2020 17:55:11 +0530 Subject: [PATCH 8/9] fixup: renaming, operator, docs --- src/Streamly/Internal/Data/Builder.hs | 70 +++++++++++++++++---------- 1 file changed, 45 insertions(+), 25 deletions(-) diff --git a/src/Streamly/Internal/Data/Builder.hs b/src/Streamly/Internal/Data/Builder.hs index d1f2baef8e..2241a6b6b6 100644 --- a/src/Streamly/Internal/Data/Builder.hs +++ b/src/Streamly/Internal/Data/Builder.hs @@ -64,28 +64,43 @@ -- -- = Usage -- --- == Using 'mk', 'bag' and ('<>') +-- == 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!" -- --- >>> b1 = mk 'h' -- Builder [] Char --- >>> b2 = b1 <> mk 'e' -- Builder [] Char --- >>> b3 = b2 <> bag "llo!" -- Builder [] Char --- >>> use b3 -- [Char] --- "hello!" +-- 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` "el" `bcons` mempty -- Builder [] Char --- >>> b2 = b1 `snoc` 'l' `snoc` 'o' -- Builder [] Char --- >>> b3 = b2 `bsnoc` " world!" -- Builder [] Char --- >>> use b3 -- [Char] +-- >>> b1 = 'h' `cons` "ello" `bcons` mempty -- Builder [] Char +-- >>> b2 = b1 `bsnoc` " world" `snoc` '!' -- Builder [] Char +-- >>> use b2 -- [Char] -- "hello world!" -- --- == Using cons and snoc operators +-- == Using 'mk', 'bag' and ('<>') -- --- >>> b1 = 'h' <+ "el" <++ mempty -- Builder [] Char --- >>> b2 = b1 +> 'l' +> 'o' -- Builder [] Char --- >>> b3 = b2 ++> " world!" -- Builder [] Char --- >>> use b3 -- [Char] +-- >>> b1 = mk 'h' <> bag "ello" -- Builder [] Char +-- >>> b2 = b1 <> bag " world" <> mk '!' -- Builder [] Char +-- >>> use b2 -- [Char] -- "hello world!" -- -- = Notes @@ -198,7 +213,8 @@ instance Monoid (Builder t a) where infixr 5 `cons` --- | Add a value at the head of the builder. +-- | Add a value at the head of the builder. Right associvative when used +-- infix. -- -- > cons a b = mk a <> b -- @@ -207,7 +223,9 @@ infixr 5 `cons` cons :: Consable t => a -> Builder t a -> Builder t a cons a b = mk a <> b --- | Same as 'cons'. +infixr 5 <+ + +-- | Same as 'cons'. Right associvative. -- -- /Internal/ -- @@ -215,7 +233,7 @@ cons a b = mk a <> b (<+) = cons -- --- | Add a value at the tail of the builder. +-- | Add a value at the tail of the builder. Left associvative when used infix. -- -- > snoc b a = b <> mk a -- @@ -224,7 +242,7 @@ cons a b = mk a <> b snoc :: Consable t => Builder t a -> a -> Builder t a snoc b a = b <> mk a --- | Same as 'snoc'. +-- | Same as 'snoc'. Left associvative. -- -- /Internal/ -- @@ -246,7 +264,8 @@ bag = Builder . (<>) infixr 5 `bcons` --- | Extend a builder by prepending a structure at the beginning. +-- | Extend a builder by prepending a structure at the beginning. Right +-- associvative when used infix. -- -- > bcons xs b = bag xs <> b -- @@ -255,16 +274,17 @@ infixr 5 `bcons` bcons :: Semigroup (t a) => t a -> Builder t a -> Builder t a bcons xs b = bag xs <> b --- | Same as 'bcons'. +infixr 5 <++ + +-- | Same as 'bcons'. Right associative. -- -- /Internal/ -- (<++) :: Semigroup (t a) => t a -> Builder t a -> Builder t a (<++) = bcons --- (++>) --- --- | Extend a builder by appending a structure at the end. +-- | Extend a builder by appending a structure at the end. Left associative +-- when used infix. -- -- > bsnoc b xs = b <> bag xs -- @@ -273,7 +293,7 @@ bcons xs b = bag xs <> b bsnoc :: Semigroup (t a) => Builder t a -> t a -> Builder t a bsnoc b xs = b <> bag xs --- | Same as 'bsnoc'. +-- | Same as 'bsnoc'. Left associative. -- -- /Internal/ -- From 7d26934fa2133c29efddfbbde45bee244253eeb8 Mon Sep 17 00:00:00 2001 From: Harendra Kumar Date: Fri, 25 Sep 2020 21:06:44 +0530 Subject: [PATCH 9/9] Add a Buildable type class So that we do not depend on the semigroup instance. Ideally, we do not want a semigroup instance in streams as it is frought with performance problems when left associated. Instead, we should use the builder to compose streams. --- benchmark/Streamly/Benchmark/Data/Builder.hs | 21 +--- src/Streamly/Internal/Data/Builder.hs | 115 ++++++++----------- 2 files changed, 52 insertions(+), 84 deletions(-) diff --git a/benchmark/Streamly/Benchmark/Data/Builder.hs b/benchmark/Streamly/Benchmark/Data/Builder.hs index f5ecfc57e8..82bef36031 100644 --- a/benchmark/Streamly/Benchmark/Data/Builder.hs +++ b/benchmark/Streamly/Benchmark/Data/Builder.hs @@ -7,7 +7,6 @@ module Main where -import Data.Functor.Identity (Identity) import Streamly.Prelude (SerialT, serially) import qualified Streamly.Internal.Data.Stream.IsStream as Stream @@ -33,7 +32,7 @@ appendListSourceR value n = {-# INLINE appendListBuilderSourceR #-} appendListBuilderSourceR :: Int -> Int -> [Int] appendListBuilderSourceR value n = - Builder.use $ foldMap (Builder.bag . (: [])) [n..n+value] + Builder.use $ foldMap (Builder.add . (: [])) [n..n+value] {-# INLINE consListBuilderSourceR #-} consListBuilderSourceR :: Int -> Int -> [Int] @@ -52,7 +51,7 @@ consStreamBuilderSourceR value n = {-# INLINE appendStreamBuilderSourceR #-} appendStreamBuilderSourceR :: Int -> Int -> SerialT m Int appendStreamBuilderSourceR value n = - Builder.use $ foldMap (Builder.bag . Stream.yield) [n..n+value] + Builder.use $ foldMap (Builder.add . Stream.yield) [n..n+value] o_1_space_appendR :: Int -> [Benchmark] o_1_space_appendR value = @@ -87,7 +86,7 @@ appendListBuilderSourceL :: Int -> Int -> [Int] appendListBuilderSourceL value n = Builder.use $ Prelude.foldl - (<>) mempty (map (Builder.bag . (: [])) [n..n+value]) + (<>) mempty (map (Builder.add . (: [])) [n..n+value]) {-# INLINE appendListMonoidBuilderSourceL #-} appendListMonoidBuilderSourceL :: Int -> Int -> [Int] @@ -114,7 +113,7 @@ appendStreamBuilderSourceL value n = $ Prelude.foldl (<>) mempty - (map (Builder.bag . Stream.yield) [n..n+value]) + (map (Builder.add . Stream.yield) [n..n+value]) {-# INLINE consStreamBuilderSourceL #-} consStreamBuilderSourceL :: Int -> Int -> SerialT m Int @@ -140,15 +139,6 @@ streamConcatStreamBuilderSourceL value n = mempty (map (Builder.mk . Stream.yield) [n..n+value]) -{-# INLINE builderConcatStreamBuilderSourceL #-} -builderConcatStreamBuilderSourceL :: Int -> Int -> SerialT Identity Int -builderConcatStreamBuilderSourceL value n = - Builder.concat - $ Prelude.foldl - (<>) - mempty - (map (Builder.mk . (Stream.yield :: Int -> SerialT Identity Int)) [n..n+value]) - o_1_space_appendL :: Int -> [Benchmark] o_1_space_appendL value = [ bgroup "appendL" @@ -186,9 +176,6 @@ o_1_space_appendL value = serially "Stream.concat stream builders" (streamConcatStreamBuilderSourceL value) - , benchPureSrc - "Builder.concat stream builders" - (builderConcatStreamBuilderSourceL value) ] ] diff --git a/src/Streamly/Internal/Data/Builder.hs b/src/Streamly/Internal/Data/Builder.hs index 2241a6b6b6..e025062586 100644 --- a/src/Streamly/Internal/Data/Builder.hs +++ b/src/Streamly/Internal/Data/Builder.hs @@ -96,10 +96,10 @@ -- >>> use b2 -- [Char] -- "hello world!" -- --- == Using 'mk', 'bag' and ('<>') +-- == Using 'mk', 'add' and ('<>') -- --- >>> b1 = mk 'h' <> bag "ello" -- Builder [] Char --- >>> b2 = b1 <> bag " world" <> mk '!' -- Builder [] Char +-- >>> b1 = mk 'h' <> add "ello" -- Builder [] Char +-- >>> b2 = b1 <> add " world" <> mk '!' -- Builder [] Char -- >>> use b2 -- [Char] -- "hello world!" -- @@ -111,21 +111,23 @@ module Streamly.Internal.Data.Builder ( Builder (..) + , Buildable (..) -- * Construction - , mk - , bag - - -- * Elimination - , use - - -- * Experimental , 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 @@ -135,24 +137,18 @@ module Streamly.Internal.Data.Builder , unfoldr -- experimental, use builder , append -- use (<>) - , bcons - , bsnoc - , (<++) - , (++>) -- ** Conversion , fromFoldable -- experimental, use foldMap mk -- ** Elimination , final - , concat -- this is of limited use perhaps ) where import Data.Semigroup (Semigroup (..)) -import Streamly.Internal.Data.Consable (Consable) - -import qualified Streamly.Internal.Data.Consable as Consable +import Streamly.Internal.Data.Stream.Serial (SerialT) +import qualified Streamly.Internal.Data.Stream.StreamK as Serial import Prelude hiding (concat) @@ -162,19 +158,28 @@ import Prelude hiding (concat) -- 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 ------------------------------------------------------------------------------- --- | Lift a single element to a builder. --- --- For streams this is 2x faster than using 'build' with singleton streams. --- --- /Internal/ --- -mk :: Consable t => a -> Builder t a -mk = Builder . Consable.cons - -- | 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)@. @@ -220,7 +225,7 @@ infixr 5 `cons` -- -- /Internal/ -- -cons :: Consable t => a -> Builder t a -> Builder t a +cons :: Buildable t => a -> Builder t a -> Builder t a cons a b = mk a <> b infixr 5 <+ @@ -229,7 +234,7 @@ infixr 5 <+ -- -- /Internal/ -- -(<+) :: Consable t => a -> Builder t a -> Builder t a +(<+) :: Buildable t => a -> Builder t a -> Builder t a (<+) = cons -- @@ -239,40 +244,31 @@ infixr 5 <+ -- -- /Internal/ -- -snoc :: Consable t => Builder t a -> a -> Builder t a +snoc :: Buildable t => Builder t a -> a -> Builder t a snoc b a = b <> mk a -- | Same as 'snoc'. Left associvative. -- -- /Internal/ -- -(+>) :: Consable t => Builder t a -> a -> Builder t a +(+>) :: Buildable t => Builder t a -> a -> Builder t a (+>) = snoc ------------------------------------------------------------------------------- -- Semigroup operations ------------------------------------------------------------------------------- --- | Lift a 'Semigroup' capable container to a builder. --- --- > bag = Builder . (<>) --- --- /Internal/ --- -bag :: Semigroup (t a) => t a -> Builder t a -bag = Builder . (<>) - infixr 5 `bcons` -- | Extend a builder by prepending a structure at the beginning. Right -- associvative when used infix. -- --- > bcons xs b = bag xs <> b +-- > bcons xs b = add xs <> b -- -- /Internal/ -- -bcons :: Semigroup (t a) => t a -> Builder t a -> Builder t a -bcons xs b = bag xs <> b +bcons :: Buildable t => t a -> Builder t a -> Builder t a +bcons xs b = add xs <> b infixr 5 <++ @@ -280,24 +276,24 @@ infixr 5 <++ -- -- /Internal/ -- -(<++) :: Semigroup (t a) => t a -> Builder t a -> Builder t a +(<++) :: 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 <> bag xs +-- > bsnoc b xs = b <> add xs -- -- /Internal/ -- -bsnoc :: Semigroup (t a) => Builder t a -> t a -> Builder t a -bsnoc b xs = b <> bag xs +bsnoc :: Buildable t => Builder t a -> t a -> Builder t a +bsnoc b xs = b <> add xs -- | Same as 'bsnoc'. Left associative. -- -- /Internal/ -- -(++>) :: Semigroup (t a) => Builder t a -> t a -> Builder t a +(++>) :: Buildable t => Builder t a -> t a -> Builder t a (++>) = bsnoc ------------------------------------------------------------------------------- @@ -313,11 +309,11 @@ bsnoc b xs = b <> bag xs -- -- /Internal/ -- -unfoldr :: Consable t => (b -> Maybe (a, b)) -> b -> Builder t a +unfoldr :: Buildable t => (b -> Maybe (a, b)) -> b -> Builder t a unfoldr step b = case step b of Nothing -> nil - Just (a, b1) -> a `cons` unfoldr step b1 + Just (a, b1) -> mk a <> unfoldr step b1 ------------------------------------------------------------------------------- -- Conversion @@ -329,21 +325,13 @@ unfoldr step b = -- -- /Internal/ -- -fromFoldable :: (Foldable t1, Consable t2) => t1 a -> Builder t2 a +fromFoldable :: (Foldable t1, Buildable t2) => t1 a -> Builder t2 a fromFoldable = foldMap mk ------------------------------------------------------------------------------- -- Elimination ------------------------------------------------------------------------------- --- | Close the builder and extract the container. --- --- /Internal/ --- -{-# INLINE use #-} -use :: Consable t => Builder t a -> t a -use (Builder k) = k Consable.nil - -- | Close a builder by appending a final container to it. -- -- This is experimental. We can always 'extendR' and 'use instead. @@ -354,18 +342,11 @@ use (Builder k) = k Consable.nil final :: Builder t a -> t a -> t a final (Builder k) = k --- | Flatten a builder building a container of containers. --- --- /Internal/ --- -concat :: (Consable t1, Foldable t1, Foldable t2) => Builder t1 (t2 a) -> t1 a -concat = foldr (\x y -> foldr Consable.cons y x) Consable.nil . use - {- -- 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 (Consable t, Foldable t) => Foldable (Builder t) where +instance (Buildable t, Foldable t) => Foldable (Builder t) where foldMap f = foldMap f . use -}