Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- type Builder = forall s. Buildable s => BuilderFor s
- newtype BuilderFor s = RawBuilder {
- unRawBuilder :: s -> BState -> BState
- type BState = (# Addr#, Addr#, State# RealWorld #)
- class Buildable s where
- byteString :: ByteString -> BuilderFor s
- flush :: BuilderFor s
- allocate :: Int -> BuilderFor s
- newtype GrowingBuffer = GrowingBuffer (IORef (ForeignPtr Word8))
- data Buffer = Buffer {}
- pattern Builder :: (s -> Buffer -> IO Buffer) -> BuilderFor s
- unBuilder :: BuilderFor s -> s -> Buffer -> IO Buffer
- byteStringCopy :: Buildable s => ByteString -> BuilderFor s
- shortByteString :: ShortByteString -> Builder
- type StrictByteStringBackend = GrowingBuffer
- toStrictByteString :: BuilderFor StrictByteStringBackend -> ByteString
- data Channel = Channel {
- chResp :: !(MVar ByteString)
- chBuffer :: !(IORef (ForeignPtr Word8))
- type LazyByteStringBackend = Channel
- toLazyByteString :: BuilderFor LazyByteStringBackend -> ByteString
- withPopper :: BuilderFor LazyByteStringBackend -> (IO ByteString -> IO a) -> IO a
- data StreamingBackend = StreamingBackend {
- sePush :: !(ByteString -> IO ())
- seBuffer :: !(IORef (ForeignPtr Word8))
- toStreamingBody :: BuilderFor StreamingBackend -> (Builder -> IO ()) -> IO () -> IO ()
- stringUtf8 :: Buildable s => String -> BuilderFor s
- lengthPrefixedWithin :: Int -> BoundedPrim Int -> BuilderFor () -> Builder
- primBounded :: Buildable s => BoundedPrim a -> a -> BuilderFor s
- primFixed :: Buildable s => FixedPrim a -> a -> BuilderFor s
- primMapListFixed :: (Foldable t, Buildable s) => FixedPrim a -> t a -> BuilderFor s
- primMapListBounded :: Buildable s => BoundedPrim a -> [a] -> BuilderFor s
- primMapByteStringFixed :: Buildable s => FixedPrim Word8 -> ByteString -> BuilderFor s
- primMapLazyByteStringFixed :: Buildable s => FixedPrim Word8 -> ByteString -> BuilderFor s
- data PutEnv = PutEnv {}
- type BufferedIOBackend = PutEnv
- hPutBuilderLen :: Handle -> BuilderFor BufferedIOBackend -> IO Int
- encodeUtf8BuilderEscaped :: Buildable s => BoundedPrim Word8 -> Text -> BuilderFor s
- sendBuilder :: Socket -> BuilderFor BufferedIOBackend -> IO Int
- cstring :: Ptr Word8 -> Builder
- cstringUtf8 :: Ptr Word8 -> Builder
- withPtr :: Buildable s => Int -> (Ptr Word8 -> IO (Ptr Word8)) -> BuilderFor s
- storable :: Storable a => a -> Builder
- paddedBoundedPrim :: Word8 -> Int -> BoundedPrim a -> a -> Builder
- zeroPaddedBoundedPrim :: Int -> BoundedPrim a -> a -> Builder
- ensure :: Int -> (Buffer -> IO Buffer) -> Builder
- allocateConstant :: (s -> IORef (ForeignPtr Word8)) -> Int -> BuilderFor s
- withGrisu3 :: Double -> IO r -> (Ptr Word8 -> Int -> Int -> IO r) -> IO r
- withGrisu3Rounded :: Int -> Double -> (Ptr Word8 -> Int -> Int -> IO r) -> IO r
- roundDigit :: Int -> Int -> Ptr Word8 -> IO Bool
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
RawBuilder | |
|
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 StreamingBackend Source # | |
Defined in Mason.Builder.Internal | |
Buildable PutEnv Source # | |
Defined in Mason.Builder.Internal byteString :: ByteString -> BuilderFor PutEnv Source # flush :: BuilderFor PutEnv Source # | |
Buildable Channel Source # | |
Defined in Mason.Builder.Internal | |
Buildable GrowingBuffer Source # | |
Defined in Mason.Builder.Internal | |
Buildable DynamicBackend Source # | |
Defined in Mason.Builder.Dynamic |
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 StrictByteStringBackend -> ByteString Source #
Create a strict ByteString
Channel | |
|
Instances
Buildable Channel Source # | |
Defined in Mason.Builder.Internal |
type LazyByteStringBackend = Channel Source #
toLazyByteString :: BuilderFor LazyByteStringBackend -> ByteString Source #
Create a lazy ByteString
. Threaded runtime is required.
withPopper :: BuilderFor LazyByteStringBackend -> (IO ByteString -> IO a) -> IO a Source #
data StreamingBackend Source #
StreamingBackend | |
|
Instances
toStreamingBody :: BuilderFor StreamingBackend -> (Builder -> IO ()) -> IO () -> IO () Source #
Convert a Builder
into a StreamingBody.
stringUtf8 :: Buildable s => String -> BuilderFor s Source #
UTF-8 encode a String
.
:: Int | maximum length |
-> BoundedPrim Int | prefix encoder |
-> BuilderFor () | |
-> Builder |
Run a builder within a buffer and prefix it by the length.
primBounded :: Buildable s => BoundedPrim a -> a -> BuilderFor s Source #
Use BoundedPrim
primMapListFixed :: (Foldable t, Buildable s) => FixedPrim a -> t a -> BuilderFor s Source #
primMapListBounded :: Buildable s => BoundedPrim a -> [a] -> BuilderFor s Source #
primMapByteStringFixed :: Buildable s => FixedPrim Word8 -> ByteString -> BuilderFor s Source #
primMapLazyByteStringFixed :: Buildable s => FixedPrim Word8 -> ByteString -> BuilderFor s Source #
Environment for handle output
Instances
Buildable PutEnv Source # | |
Defined in Mason.Builder.Internal byteString :: ByteString -> BuilderFor PutEnv Source # flush :: BuilderFor PutEnv Source # |
type BufferedIOBackend = PutEnv Source #
hPutBuilderLen :: Handle -> BuilderFor BufferedIOBackend -> 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.
encodeUtf8BuilderEscaped :: Buildable s => BoundedPrim Word8 -> Text -> BuilderFor s Source #
Encode Text
with a custom escaping function
sendBuilder :: Socket -> BuilderFor BufferedIOBackend -> IO Int Source #
Write a Builder
into a handle and obtain the number of bytes written.
:: Buildable s | |
=> Int | number of bytes to allocate (if needed) |
-> (Ptr Word8 -> IO (Ptr Word8)) | return a next pointer after writing |
-> BuilderFor s |
Construct a Builder
from a "poke" function.
:: Word8 | filler |
-> Int | pad if shorter than this |
-> BoundedPrim a | |
-> a | |
-> Builder |
zeroPaddedBoundedPrim :: Int -> BoundedPrim a -> a -> Builder Source #
Internal
ensure :: Int -> (Buffer -> IO Buffer) -> Builder Source #
Ensure that the given number of bytes is available in the buffer. Subject to semigroup fusion
allocateConstant :: (s -> IORef (ForeignPtr Word8)) -> Int -> BuilderFor s Source #
Allocate a new buffer.