{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TypeApplications #-}
{-# OPTIONS_GHC -ddump-splices #-}
module Generics.POSable.TH (mkPOSableGround) where
import Generics.POSable.POSable
import Generics.POSable.Representation
import Language.Haskell.TH
mkPOSableGround :: Name -> DecsQ
mkPOSableGround :: Name -> DecsQ
mkPOSableGround Name
name = Q Type -> DecsQ
mkDec (Type -> Q Type
forall (f :: Type -> Type) a. Applicative f => a -> f a
pure (Name -> Type
ConT Name
name))
mkDec :: Q Type -> DecsQ
mkDec :: Q Type -> DecsQ
mkDec Q Type
name =
[d| instance POSable $name where
type Choices $name = 1
choices _ = 0
type Fields $name = '[ '[$name]]
fields x = Cons (Pick x) Nil
tags = [1]
fromPOSable 0 (Cons (Pick x) Nil) = x
fromPOSable _ _ = error "index out of range"
emptyFields = PTCons (STSucc (mkGround @($name)) STZero) PTNil
|]