module Foundation.Collection.Buildable
( Buildable(..)
, Builder(..)
, BuildingState(..)
, builderLift
, build_
) where
import Basement.UArray
import Basement.UArray.Mutable
import qualified Basement.BoxedArray as BA
import qualified Basement.String as S
import Foundation.Collection.Element
import Basement.Compat.Base
import Basement.Monad
import Basement.MutableBuilder
import Basement.Compat.MonadTrans
class Buildable col where
type Mutable col :: * -> *
type Step col
append :: (PrimMonad prim) => Element col -> Builder col (Mutable col) (Step col) prim err ()
build :: (PrimMonad prim)
=> Int
-> Builder col (Mutable col) (Step col) prim err ()
-> prim (Either err col)
builderLift :: (Buildable c, PrimMonad prim)
=> prim a
-> Builder c (Mutable c) (Step c) prim err a
builderLift f = Builder $ State $ \(i, st, e) -> do
ret <- f
return (ret, (i, st, e))
build_ :: (Buildable c, PrimMonad prim)
=> Int
-> Builder c (Mutable c) (Step c) prim () ()
-> prim c
build_ sizeChunksI ab = either (\() -> internalError "impossible output") id <$> build sizeChunksI ab
instance PrimType ty => Buildable (UArray ty) where
type Mutable (UArray ty) = MUArray ty
type Step (UArray ty) = ty
append = builderAppend
build = builderBuild
instance Buildable (BA.Array ty) where
type Mutable (BA.Array ty) = BA.MArray ty
type Step (BA.Array ty) = ty
append = BA.builderAppend
build = BA.builderBuild
instance Buildable S.String where
type Mutable S.String = S.MutableString
type Step S.String = Word8
append = S.builderAppend
build = S.builderBuild