{-# LANGUAGE CPP #-}
{-# LANGUAGE RankNTypes #-}
module Codec.Serialise
(
serialise
, deserialise
, deserialiseOrFail
, CBOR.Read.DeserialiseFailure(..)
, serialiseIncremental
, deserialiseIncremental
, CBOR.Read.IDecode(..)
, Serialise(..)
, writeFileSerialise
, readFileDeserialise
, hPutSerialise
) where
import Control.Monad.ST
import System.IO (Handle, IOMode (..), withFile)
import Control.Exception (throw, throwIO)
import qualified Data.ByteString.Builder as BS
import qualified Data.ByteString.Lazy as BS
import qualified Data.ByteString.Lazy.Internal as BS
import Codec.Serialise.Class
import qualified Codec.CBOR.Read as CBOR.Read
import qualified Codec.CBOR.Write as CBOR.Write
serialiseIncremental :: Serialise a => a -> BS.Builder
serialiseIncremental :: forall a. Serialise a => a -> Builder
serialiseIncremental = Encoding -> Builder
CBOR.Write.toBuilder forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Serialise a => a -> Encoding
encode
deserialiseIncremental :: Serialise a => ST s (CBOR.Read.IDecode s a)
deserialiseIncremental :: forall a s. Serialise a => ST s (IDecode s a)
deserialiseIncremental = forall s a. Decoder s a -> ST s (IDecode s a)
CBOR.Read.deserialiseIncremental forall a s. Serialise a => Decoder s a
decode
serialise :: Serialise a => a -> BS.ByteString
serialise :: forall a. Serialise a => a -> ByteString
serialise = Encoding -> ByteString
CBOR.Write.toLazyByteString forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Serialise a => a -> Encoding
encode
deserialise :: Serialise a => BS.ByteString -> a
deserialise :: forall a. Serialise a => ByteString -> a
deserialise ByteString
bs0 =
forall a. (forall s. ST s a) -> a
runST (forall {s} {a}. ByteString -> IDecode s a -> ST s a
supplyAllInput ByteString
bs0 forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< forall a s. Serialise a => ST s (IDecode s a)
deserialiseIncremental)
where
supplyAllInput :: ByteString -> IDecode s a -> ST s a
supplyAllInput ByteString
_bs (CBOR.Read.Done ByteString
_ ByteOffset
_ a
x) = forall (m :: * -> *) a. Monad m => a -> m a
return a
x
supplyAllInput ByteString
bs (CBOR.Read.Partial Maybe ByteString -> ST s (IDecode s a)
k) =
case ByteString
bs of
BS.Chunk ByteString
chunk ByteString
bs' -> Maybe ByteString -> ST s (IDecode s a)
k (forall a. a -> Maybe a
Just ByteString
chunk) forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ByteString -> IDecode s a -> ST s a
supplyAllInput ByteString
bs'
ByteString
BS.Empty -> Maybe ByteString -> ST s (IDecode s a)
k forall a. Maybe a
Nothing forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ByteString -> IDecode s a -> ST s a
supplyAllInput ByteString
BS.Empty
supplyAllInput ByteString
_ (CBOR.Read.Fail ByteString
_ ByteOffset
_ DeserialiseFailure
exn) = forall a e. Exception e => e -> a
throw DeserialiseFailure
exn
deserialiseOrFail :: Serialise a => BS.ByteString -> Either CBOR.Read.DeserialiseFailure a
deserialiseOrFail :: forall a. Serialise a => ByteString -> Either DeserialiseFailure a
deserialiseOrFail ByteString
bs0 =
forall a. (forall s. ST s a) -> a
runST (forall {s} {b}.
ByteString -> IDecode s b -> ST s (Either DeserialiseFailure b)
supplyAllInput ByteString
bs0 forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< forall a s. Serialise a => ST s (IDecode s a)
deserialiseIncremental)
where
supplyAllInput :: ByteString -> IDecode s b -> ST s (Either DeserialiseFailure b)
supplyAllInput ByteString
_bs (CBOR.Read.Done ByteString
_ ByteOffset
_ b
x) = forall (m :: * -> *) a. Monad m => a -> m a
return (forall a b. b -> Either a b
Right b
x)
supplyAllInput ByteString
bs (CBOR.Read.Partial Maybe ByteString -> ST s (IDecode s b)
k) =
case ByteString
bs of
BS.Chunk ByteString
chunk ByteString
bs' -> Maybe ByteString -> ST s (IDecode s b)
k (forall a. a -> Maybe a
Just ByteString
chunk) forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ByteString -> IDecode s b -> ST s (Either DeserialiseFailure b)
supplyAllInput ByteString
bs'
ByteString
BS.Empty -> Maybe ByteString -> ST s (IDecode s b)
k forall a. Maybe a
Nothing forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ByteString -> IDecode s b -> ST s (Either DeserialiseFailure b)
supplyAllInput ByteString
BS.Empty
supplyAllInput ByteString
_ (CBOR.Read.Fail ByteString
_ ByteOffset
_ DeserialiseFailure
exn) = forall (m :: * -> *) a. Monad m => a -> m a
return (forall a b. a -> Either a b
Left DeserialiseFailure
exn)
hPutSerialise :: Serialise a
=> Handle
-> a
-> IO ()
hPutSerialise :: forall a. Serialise a => Handle -> a -> IO ()
hPutSerialise Handle
hnd a
x = Handle -> ByteString -> IO ()
BS.hPut Handle
hnd (forall a. Serialise a => a -> ByteString
serialise a
x)
writeFileSerialise :: Serialise a
=> FilePath
-> a
-> IO ()
writeFileSerialise :: forall a. Serialise a => FilePath -> a -> IO ()
writeFileSerialise FilePath
fname a
x =
forall r. FilePath -> IOMode -> (Handle -> IO r) -> IO r
withFile FilePath
fname IOMode
WriteMode forall a b. (a -> b) -> a -> b
$ \Handle
hnd -> forall a. Serialise a => Handle -> a -> IO ()
hPutSerialise Handle
hnd a
x
readFileDeserialise :: Serialise a
=> FilePath
-> IO a
readFileDeserialise :: forall a. Serialise a => FilePath -> IO a
readFileDeserialise FilePath
fname =
forall r. FilePath -> IOMode -> (Handle -> IO r) -> IO r
withFile FilePath
fname IOMode
ReadMode forall a b. (a -> b) -> a -> b
$ \Handle
hnd -> do
ByteString
input <- Handle -> IO ByteString
BS.hGetContents Handle
hnd
case forall a. Serialise a => ByteString -> Either DeserialiseFailure a
deserialiseOrFail ByteString
input of
Left DeserialiseFailure
err -> forall e a. Exception e => e -> IO a
throwIO DeserialiseFailure
err
Right a
x -> forall (m :: * -> *) a. Monad m => a -> m a
return a
x