{-# language BangPatterns #-}
module Data.Builder.ST
( Builder(..)
, new
, push
, freeze
) where
import Data.Primitive (SmallMutableArray)
import Control.Monad.ST (ST)
import Data.Primitive (newSmallArray,writeSmallArray,unsafeFreezeSmallArray)
import Data.Primitive (sizeofSmallArray,freezeSmallArray)
import Data.Chunks (Chunks(ChunksNil,ChunksCons))
import Foreign.Storable (sizeOf)
import qualified Data.Chunks as C
data Builder s a = Builder
!(SmallMutableArray s a)
!Int
!Int
!(Chunks a)
new :: ST s (Builder s a)
new = do
marr <- newSmallArray initialLength errorThunk
pure (Builder marr 0 initialLength ChunksNil)
push ::
a
-> Builder s a
-> ST s (Builder s a)
push a (Builder marr off len cs) = case len > 0 of
True -> do
writeSmallArray marr off a
pure $! Builder marr (off + 1) (len - 1) cs
False -> do
arr <- unsafeFreezeSmallArray marr
let lenNew = nextLength (sizeofSmallArray arr)
marrNew <- newSmallArray lenNew a
let !csNew = ChunksCons arr cs
pure $! Builder marrNew 1 (lenNew - 1) csNew
nextLength :: Int -> Int
nextLength i = if i < maxElementCount - smallArrayHeaderWords
then i * 2 + smallArrayHeaderWords
else maxElementCount - smallArrayHeaderWords
maxElementCount :: Int
maxElementCount = div 4096 (sizeOf (undefined :: Int))
initialLength :: Int
initialLength = 16 - smallArrayHeaderWords
smallArrayHeaderWords :: Int
smallArrayHeaderWords = 2
freeze ::
Builder s a
-> ST s (Chunks a)
freeze (Builder marr off _ cs) = do
arr <- freezeSmallArray marr 0 off
pure $! C.reverseOnto (ChunksCons arr ChunksNil) cs
errorThunk :: a
{-# noinline errorThunk #-}
errorThunk = error "array-builder:Data.Builder.ST: error"