{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE CPP #-}
module Flat.Filler (
Filler(..),
fillerLength,
PreAligned(..),
preAligned,
PostAligned(..),
postAligned,
postAlignedDecoder
) where
import Flat.Class
import Flat.Encoder
import Flat.Decoder
import Control.DeepSeq
import Data.Typeable
data Filler = FillerBit Filler
| FillerEnd
deriving (Show, Eq, Ord, Typeable, Generic, NFData)
instance Flat Filler where
encode _ = eFiller
size = sFillerMax
data PostAligned a = PostAligned { postValue :: a, postFiller :: Filler }
#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
data PreAligned a = PreAligned { preFiller :: Filler, preValue :: a }
deriving (Show, Eq, Ord, Typeable, Generic, NFData, Flat)
fillerLength :: Num a => Filler -> a
fillerLength FillerEnd = 1
fillerLength (FillerBit f) = 1 + fillerLength f
postAligned :: a -> PostAligned a
postAligned a = PostAligned a FillerEnd
preAligned :: a -> PreAligned a
preAligned = PreAligned FillerEnd
postAlignedDecoder :: Get b -> Get b
postAlignedDecoder dec = do
v <- dec
_::Filler <- decode
return v