module Binrep.Example.Sum where import Binrep import Data.Word import GHC.Generics ( type Generic ) import Generic.Data.FOnCstr data SumType = SumType1 Word8 | SumType2 Word8 Word8 deriving stock ((forall x. SumType -> Rep SumType x) -> (forall x. Rep SumType x -> SumType) -> Generic SumType forall x. Rep SumType x -> SumType forall x. SumType -> Rep SumType x forall a. (forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a $cfrom :: forall x. SumType -> Rep SumType x from :: forall x. SumType -> Rep SumType x $cto :: forall x. Rep SumType x -> SumType to :: forall x. Rep SumType x -> SumType Generic, Int -> SumType -> ShowS [SumType] -> ShowS SumType -> String (Int -> SumType -> ShowS) -> (SumType -> String) -> ([SumType] -> ShowS) -> Show SumType forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a $cshowsPrec :: Int -> SumType -> ShowS showsPrec :: Int -> SumType -> ShowS $cshow :: SumType -> String show :: SumType -> String $cshowList :: [SumType] -> ShowS showList :: [SumType] -> ShowS Show) instance Get SumType where get :: Getter SumType get = do forall a. Get a => Getter a get @Word8 Getter Word8 -> (Word8 -> Getter SumType) -> Getter SumType forall a b. ParserT PureMode (ParseError Pos Builder) a -> (a -> ParserT PureMode (ParseError Pos Builder) b) -> ParserT PureMode (ParseError Pos Builder) b forall (m :: Type -> Type) a b. Monad m => m a -> (a -> m b) -> m b >>= \case Word8 1 -> forall {k} (tag :: k) (name :: Symbol) a. (Generic a, Functor (GenericFOnCstrF tag), GFOnCstr tag name (Rep a)) => GenericFOnCstrF tag a forall (tag :: Type -> Constraint) (name :: Symbol) a. (Generic a, Functor (GenericFOnCstrF tag), GFOnCstr tag name (Rep a)) => GenericFOnCstrF tag a genericFOnCstr @Get @"SumType1" Word8 2 -> forall {k} (tag :: k) (name :: Symbol) a. (Generic a, Functor (GenericFOnCstrF tag), GFOnCstr tag name (Rep a)) => GenericFOnCstrF tag a forall (tag :: Type -> Constraint) (name :: Symbol) a. (Generic a, Functor (GenericFOnCstrF tag), GFOnCstr tag name (Rep a)) => GenericFOnCstrF tag a genericFOnCstr @Get @"SumType2" Word8 _ -> String -> Getter SumType forall a. HasCallStack => String -> a error String "TODO"