Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- type Builder = forall s. Buildable s => BuilderFor s
- newtype BuilderFor s = Builder {}
- class Buildable s where
- byteString :: ByteString -> BuilderFor s
- flush :: BuilderFor s
- allocate :: Int -> BuilderFor s
- newtype GrowingBuffer = GrowingBuffer (IORef (ForeignPtr Word8))
- data Buffer = Buffer {}
- byteStringCopy :: Buildable s => ByteString -> BuilderFor s
- shortByteString :: ShortByteString -> Builder
- toStrictByteString :: BuilderFor GrowingBuffer -> ByteString
- data Channel = Channel {
- chResp :: !(MVar ByteString)
- chBuffer :: !(IORef (ForeignPtr Word8))
- toLazyByteString :: BuilderFor Channel -> ByteString
- stringUtf8 :: String -> Builder
- lengthPrefixedWithin :: Int -> BoundedPrim Int -> BuilderFor () -> Builder
- primBounded :: BoundedPrim a -> a -> Builder
- primFixed :: FixedPrim a -> a -> Builder
- primMapListFixed :: FixedPrim a -> [a] -> Builder
- primMapListBounded :: BoundedPrim a -> [a] -> Builder
- primMapByteStringFixed :: FixedPrim Word8 -> ByteString -> Builder
- primMapLazyByteStringFixed :: FixedPrim Word8 -> ByteString -> Builder
- hPutBuilderLen :: Handle -> BuilderFor PutBuilderEnv -> IO Int
- data PutBuilderEnv = PBE {}
- encodeUtf8BuilderEscaped :: BoundedPrim Word8 -> Text -> Builder
- sendBuilder :: Socket -> BuilderFor SocketEnv -> IO Int
- data SocketEnv = SE {}
- cstring :: Ptr Word8 -> Builder
- cstringUtf8 :: Ptr Word8 -> Builder
- ensure :: Int -> (Buffer -> IO Buffer) -> Builder
- allocateConstant :: (s -> IORef (ForeignPtr Word8)) -> Int -> BuilderFor s
- grisu3 :: Double -> Maybe (ByteString, Int)
Documentation
type Builder = forall s. Buildable s => BuilderFor s Source #
The Builder type. Requires RankNTypes extension
newtype BuilderFor s Source #
Builder specialised for a backend
Instances
Buildable s => IsString (BuilderFor s) Source # | |
Defined in Mason.Builder.Internal fromString :: String -> BuilderFor s # | |
Semigroup (BuilderFor s) Source # | |
Defined in Mason.Builder.Internal (<>) :: BuilderFor s -> BuilderFor s -> BuilderFor s # sconcat :: NonEmpty (BuilderFor s) -> BuilderFor s # stimes :: Integral b => b -> BuilderFor s -> BuilderFor s # | |
Monoid (BuilderFor a) Source # | |
Defined in Mason.Builder.Internal mempty :: BuilderFor a # mappend :: BuilderFor a -> BuilderFor a -> BuilderFor a # mconcat :: [BuilderFor a] -> BuilderFor a # |
class Buildable s where Source #
This class is used to provide backend-specific operations for running a Builder
.
byteString :: ByteString -> BuilderFor s Source #
Put a ByteString
.
flush :: BuilderFor s Source #
Flush the content of the internal buffer.
allocate :: Int -> BuilderFor s Source #
Allocate a buffer with at least the given length.
Instances
Buildable () Source # | Work with a constant buffer. |
Defined in Mason.Builder.Internal byteString :: ByteString -> BuilderFor () Source # flush :: BuilderFor () Source # allocate :: Int -> BuilderFor () Source # | |
Buildable SocketEnv Source # | |
Defined in Mason.Builder.Internal | |
Buildable PutBuilderEnv Source # | |
Defined in Mason.Builder.Internal | |
Buildable Channel Source # | |
Defined in Mason.Builder.Internal | |
Buildable GrowingBuffer Source # | |
Defined in Mason.Builder.Internal |
newtype GrowingBuffer Source #
Instances
Buildable GrowingBuffer Source # | |
Defined in Mason.Builder.Internal |
Buffer pointers
byteStringCopy :: Buildable s => ByteString -> BuilderFor s Source #
Copy a ByteString
to a buffer.
shortByteString :: ShortByteString -> Builder Source #
Copy a ShortByteString
to a buffer.
toStrictByteString :: BuilderFor GrowingBuffer -> ByteString Source #
Create a strict ByteString
Channel | |
|
Instances
Buildable Channel Source # | |
Defined in Mason.Builder.Internal |
toLazyByteString :: BuilderFor Channel -> ByteString Source #
Create a lazy ByteString
. Threaded runtime is required.
:: Int | maximum length |
-> BoundedPrim Int | prefix encoder |
-> BuilderFor () | |
-> Builder |
Run a builder within a buffer and prefix it by the length.
primBounded :: BoundedPrim a -> a -> Builder Source #
Use BoundedPrim
primMapListFixed :: FixedPrim a -> [a] -> Builder Source #
primMapListBounded :: BoundedPrim a -> [a] -> Builder Source #
primMapByteStringFixed :: FixedPrim Word8 -> ByteString -> Builder Source #
hPutBuilderLen :: Handle -> BuilderFor PutBuilderEnv -> IO Int Source #
Write a Builder
into a handle and obtain the number of bytes written.
flush
does not imply actual disk operations. Set NoBuffering
if you want
it to write the content immediately.
data PutBuilderEnv Source #
Environemnt for handle output
Instances
Buildable PutBuilderEnv Source # | |
Defined in Mason.Builder.Internal |
encodeUtf8BuilderEscaped :: BoundedPrim Word8 -> Text -> Builder Source #
Encode Text
with a custom escaping function
sendBuilder :: Socket -> BuilderFor SocketEnv -> IO Int Source #
Write a Builder
into a handle and obtain the number of bytes written.
Environemnt for socket output
Instances
Buildable SocketEnv Source # | |
Defined in Mason.Builder.Internal |
Internal
ensure :: Int -> (Buffer -> IO Buffer) -> Builder Source #
Ensure that the given number of bytes is available in the buffer. Subject to semigroup fusions
allocateConstant :: (s -> IORef (ForeignPtr Word8)) -> Int -> BuilderFor s Source #
Allocate a new buffer.