feat[types]: ConstantPool uses GADT instead of data family

This commit is contained in:
vegowotenks 2025-07-13 11:57:08 +02:00
parent f85f3f8b79
commit 2d079b5873

View file

@ -8,6 +8,8 @@
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE StandaloneDeriving #-}
module Language.Java.Classfile.ConstantPool (ConstantPool(..)) where
import Data.Word (Word16)
import Data.Array.IArray (Array, listArray)
@ -18,15 +20,15 @@ import qualified Data.Text as Text
import Language.Java.Classfile.Stage (Stage(..))
import Data.Kind (Type)
type ConstantPool :: Stage -> Type
data ConstantPool stage where
ConstantPool :: (Array Word16 Entry) -> ConstantPool Parse
NoPool :: ConstantPool Resolve
deriving instance Show (ConstantPool stage)
-- | 'Stage'-indexed constant-pool. The constant-pool is erased after resolving the class file.
type ConstantPool :: Stage -> Type
data family ConstantPool stage
newtype instance ConstantPool Parse = ConstantPool (Array Word16 Entry)
deriving stock (Show)
data instance ConstantPool Resolve = NoPool
instance Extractable (ConstantPool Parse) where
extract :: Extract (ConstantPool Parse)