| Safe Haskell | None | 
|---|
Haste.Binary
Description
Handling of Javascript-native binary blobs.
- type Put = PutM ()
 - data PutM a
 - putWord8 :: Word8 -> Put
 - putWord16le :: Word16 -> Put
 - putWord32le :: Word32 -> Put
 - putInt8 :: Int8 -> Put
 - putInt16le :: Int16 -> Put
 - putInt32le :: Int32 -> Put
 - putFloat32le :: Float -> Put
 - putFloat64le :: Double -> Put
 - putBlob :: Blob -> Put
 - runPut :: Put -> Blob
 - data Get a
 - getWord8 :: Get Word8
 - getWord16le :: Get Word16
 - getWord32le :: Get Word32
 - getInt8 :: Get Int8
 - getInt16le :: Get Int16
 - getInt32le :: Get Int32
 - getFloat32le :: Get Float
 - getFloat64le :: Get Double
 - getBytes :: Int -> Get BlobData
 - skip :: Int -> Get ()
 - runGet :: Get a -> BlobData -> Either String a
 - class Monad m => MonadBlob m  where
- getBlobData :: Blob -> m BlobData
 - getBlobText :: Blob -> m String
 
 - class Binary a where
 - data Blob
 - data BlobData
 - blobSize :: Blob -> Int
 - blobDataSize :: BlobData -> Int
 - toByteString :: BlobData -> ByteString
 - toBlob :: BlobData -> Blob
 - strToBlob :: JSString -> Blob
 - encode :: Binary a => a -> Blob
 - decode :: Binary a => BlobData -> Either String a
 
Documentation
putWord16le :: Word16 -> PutSource
putWord32le :: Word32 -> PutSource
putInt16le :: Int16 -> PutSource
putInt32le :: Int32 -> PutSource
putFloat32le :: Float -> PutSource
putFloat64le :: Double -> PutSource
class Monad m => MonadBlob m whereSource
Methods
getBlobData :: Blob -> m BlobDataSource
Retrieve the raw data from a blob.
getBlobText :: Blob -> m StringSource
Interpret a blob as UTF-8 text.
Somewhat efficient serializationdeserialization tofrom binary Blobs. The layout of the binaries producedread by getput and encode/decode may change between versions. If you need a stable binary format, you should make your own using the primitives in Haste.Binary.Get/Put.
blobDataSize :: BlobData -> IntSource
The size, in bytes, of the contents of the given blob data.
toByteString :: BlobData -> ByteStringSource
Convert a BlobData to a ByteString. Only usable server-side.