{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeInType #-}
{-# LANGUAGE TypeOperators #-}
module Codec.Scale.Generic () where
import Data.Serialize.Get (Get, getWord8)
import Data.Serialize.Put (PutM, putWord8)
import Data.Word (Word8)
import Generics.SOP (All, Compose, I (..), NP (..), NS (..),
SOP (..), unSOP, unZ)
import Codec.Scale.Class (Decode (..), Encode (..), GDecode (..),
GEncode (..))
instance ( GEncode (NP f xs)
, GEncode (NP f ys)
, All (GEncode `Compose` NP f) xss
) => GEncode (SOP f (xs ': ys ': xss)) where
gPut = go 0 . unSOP
where
go :: forall f as . All (GEncode `Compose` f) as => Word8 -> NS f as -> PutM ()
go !acc (Z x) = putWord8 acc >> gPut x
go !acc (S x) = go (acc + 1) x
instance GEncode (NP f xs) => GEncode (SOP f '[xs]) where
gPut = gPut . unZ . unSOP
instance (Encode a, GEncode (NP I as)) => GEncode (NP I (a ': as)) where
gPut (I a :* as) = put a >> gPut as
instance GEncode (NP I '[]) where
gPut _ = mempty
class EnumParser xs where
enumParser :: All (GDecode `Compose` NP f) xs => Word8 -> Get (NS (NP f) xs)
instance EnumParser as => EnumParser (a ': as) where
enumParser !i | i > 0 = S <$> enumParser (i - 1)
| otherwise = Z <$> gGet
instance EnumParser '[] where
enumParser _ = fail "wrong prefix during enum decoding"
instance ( GDecode (NP f xs)
, GDecode (NP f ys)
, All (GDecode `Compose` NP f) xss
, EnumParser xss
) => GDecode (SOP f (xs ': ys ': xss)) where
gGet = SOP <$> (enumParser =<< getWord8)
instance GDecode (NP f as) => GDecode (SOP f '[as]) where
gGet = SOP . Z <$> gGet
instance (Decode a, GDecode (NP I as)) => GDecode (NP I (a ': as)) where
gGet = (:*) <$> (I <$> get) <*> gGet
instance GDecode (NP I '[]) where
gGet = return Nil