{-# LANGUAGE CPP #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
module Flat.Run (
flat,
flatRaw,
unflat,
unflatWith,
unflatRaw,
unflatRawWith,
) where
import qualified Data.ByteString as B
import Data.ByteString.Convert (AsByteString (..))
import Flat.Class (Flat (decode, encode), getSize)
import Flat.Decoder (Decoded, Get, strictDecoder)
import qualified Flat.Encoder as E
import Flat.Filler (postAligned, postAlignedDecoder)
flat :: Flat a => a -> B.ByteString
flat :: a -> ByteString
flat = PostAligned a -> ByteString
forall a b. (Flat a, AsByteString b) => a -> b
flatRaw (PostAligned a -> ByteString)
-> (a -> PostAligned a) -> a -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> PostAligned a
forall a. a -> PostAligned a
postAligned
unflat :: (Flat a, AsByteString b) => b -> Decoded a
unflat :: b -> Decoded a
unflat = Get a -> b -> Decoded a
forall b a. AsByteString b => Get a -> b -> Decoded a
unflatWith Get a
forall a. Flat a => Get a
decode
unflatWith :: AsByteString b => Get a -> b -> Decoded a
unflatWith :: Get a -> b -> Decoded a
unflatWith Get a
dec = Get a -> b -> Decoded a
forall b a. AsByteString b => Get a -> b -> Decoded a
unflatRawWith (Get a -> Get a
forall b. Get b -> Get b
postAlignedDecoder Get a
dec)
unflatRaw :: (Flat a, AsByteString b) => b -> Decoded a
unflatRaw :: b -> Decoded a
unflatRaw = Get a -> b -> Decoded a
forall b a. AsByteString b => Get a -> b -> Decoded a
unflatRawWith Get a
forall a. Flat a => Get a
decode
unflatRawWith :: AsByteString b => Get a -> b -> Decoded a
unflatRawWith :: Get a -> b -> Decoded a
unflatRawWith Get a
dec = Get a -> ByteString -> Decoded a
forall a. Get a -> ByteString -> Either DecodeException a
strictDecoder Get a
dec (ByteString -> Decoded a) -> (b -> ByteString) -> b -> Decoded a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. b -> ByteString
forall a. AsByteString a => a -> ByteString
toByteString
flatRaw :: (Flat a, AsByteString b) => a -> b
flatRaw :: a -> b
flatRaw a
a =
ByteString -> b
forall a. AsByteString a => ByteString -> a
fromByteString (ByteString -> b) -> ByteString -> b
forall a b. (a -> b) -> a -> b
$
NumBits -> Encoding -> ByteString
E.strictEncoder
(a -> NumBits
forall a. Flat a => a -> NumBits
getSize a
a)
#ifdef ETA_VERSION
(E.trampolineEncoding (encode a))
#else
(a -> Encoding
forall a. Flat a => a -> Encoding
encode a
a)
#endif