module Binrep.Put where

import Mason.Builder qualified as Mason

import Data.ByteString qualified as B

import Data.Word
import Data.Int
import Data.Void ( Void, absurd )

type Builder = Mason.BuilderFor Mason.StrictByteStringBackend

class Put a where
    -- | Serialize to binary.
    put :: a -> Builder

-- | Run the serializer.
runPut :: Put a => a -> B.ByteString
runPut :: forall a. Put a => a -> ByteString
runPut = Builder -> ByteString
runBuilder forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Put a => a -> Builder
put

runBuilder :: Builder -> B.ByteString
runBuilder :: Builder -> ByteString
runBuilder = Builder -> ByteString
Mason.toStrictByteString

-- | Impossible to serialize 'Void'.
instance Put Void where
    put :: Void -> Builder
put = forall a. Void -> a
absurd

-- | Serialize each element in order. No length indicator, so parse until either
--   error or EOF. Usually not what you want, but sometimes used at the "top" of
--   binary formats.
instance Put a => Put [a] where
    put :: [a] -> Builder
put = forall a. Monoid a => [a] -> a
mconcat forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a -> b) -> [a] -> [b]
map forall a. Put a => a -> Builder
put

instance (Put a, Put b) => Put (a, b) where
    put :: (a, b) -> Builder
put (a
a, b
b) = forall a. Put a => a -> Builder
put a
a forall a. Semigroup a => a -> a -> a
<> forall a. Put a => a -> Builder
put b
b

-- | Serialize the bytestring as-is.
--
-- Careful -- the only way you're going to be able to parse this is to read
-- until EOF.
instance Put B.ByteString where
    put :: ByteString -> Builder
put = forall s. Buildable s => ByteString -> BuilderFor s
Mason.byteString
    {-# INLINE put #-}

-- need to give args for RankNTypes reasons I don't understand
instance Put Word8 where
    put :: Word8 -> Builder
put Word8
w = Word8 -> Builder
Mason.word8 Word8
w
    {-# INLINE put #-}
instance Put  Int8 where
    put :: Int8 -> Builder
put Int8
w = Int8 -> Builder
Mason.int8 Int8
w
    {-# INLINE put #-}

-- | Put with inlined checks via an environment.
class PutWith r a where
    -- | Attempt to serialize to binary with the given environment.
    putWith :: r -> a -> Either String Builder
    default putWith :: Put a => r -> a -> Either String Builder
    putWith r
_ = forall a. Put a => a -> Either String Builder
putWithout

-- | Helper for wrapping a 'BinRep' into a 'BinRepWith' (for encoding).
putWithout :: Put a => a -> Either String Builder
putWithout :: forall a. Put a => a -> Either String Builder
putWithout = forall a b. b -> Either a b
Right forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Put a => a -> Builder
put

instance Put a => PutWith r [a]

-- | Run the serializer with the given environment.
runPutWith :: PutWith r a => r -> a -> Either String B.ByteString
runPutWith :: forall r a. PutWith r a => r -> a -> Either String ByteString
runPutWith r
r a
a = case forall r a. PutWith r a => r -> a -> Either String Builder
putWith r
r a
a of Left  String
e -> forall a b. a -> Either a b
Left String
e
                                     Right Builder
x -> forall a b. b -> Either a b
Right forall a b. (a -> b) -> a -> b
$ Builder -> ByteString
runBuilder Builder
x