{-# LANGUAGE CPP #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}

-- |Encoding and decoding functions
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)

-- |Encode padded value.
flat :: Flat a => a -> B.ByteString
flat :: forall a. Flat a => a -> ByteString
flat = forall a b. (Flat a, AsByteString b) => a -> b
flatRaw forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. a -> PostAligned a
postAligned

-- |Decode padded value.
unflat :: (Flat a, AsByteString b) => b -> Decoded a
unflat :: forall a b. (Flat a, AsByteString b) => b -> Decoded a
unflat = forall b a. AsByteString b => Get a -> b -> Decoded a
unflatWith forall a. Flat a => Get a
decode

-- |Decode padded value, using the provided unpadded decoder.
unflatWith :: AsByteString b => Get a -> b -> Decoded a
unflatWith :: forall b a. AsByteString b => Get a -> b -> Decoded a
unflatWith Get a
dec = forall b a. AsByteString b => Get a -> b -> Decoded a
unflatRawWith (forall b. Get b -> Get b
postAlignedDecoder Get a
dec)

-- |Decode unpadded value.
unflatRaw :: (Flat a, AsByteString b) => b -> Decoded a
unflatRaw :: forall a b. (Flat a, AsByteString b) => b -> Decoded a
unflatRaw = forall b a. AsByteString b => Get a -> b -> Decoded a
unflatRawWith forall a. Flat a => Get a
decode

-- |Unflat unpadded value, using provided decoder
unflatRawWith :: AsByteString b => Get a -> b -> Decoded a
unflatRawWith :: forall b a. AsByteString b => Get a -> b -> Decoded a
unflatRawWith Get a
dec = forall a. Get a -> ByteString -> Either DecodeException a
strictDecoder Get a
dec forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. AsByteString a => a -> ByteString
toByteString

-- |Encode unpadded value
flatRaw :: (Flat a, AsByteString b) => a -> b
flatRaw :: forall a b. (Flat a, AsByteString b) => a -> b
flatRaw a
a =
    forall a. AsByteString a => ByteString -> a
fromByteString forall a b. (a -> b) -> a -> b
$
        NumBits -> Encoding -> ByteString
E.strictEncoder
            (forall a. Flat a => a -> NumBits
getSize a
a)

#ifdef ETA_VERSION
        (E.trampolineEncoding (encode a))
#else
        (forall a. Flat a => a -> Encoding
encode a
a)
#endif

-- #ifdef ETA_VERSION
--   deriving (Show, Eq, Ord, Typeable, Generic, NFData)

-- instance Flat a => Flat (PostAligned a) where
--   encode (PostAligned val fill) = trampolineEncoding (encode val) <> encode fill

-- #else
--   deriving (Show, Eq, Ord, Typeable, Generic, NFData,Flat)
-- #endif