feat[classfile]: stages the entire file

This commit is contained in:
vegowotenks 2025-08-21 08:54:36 +02:00
parent 500bfa349e
commit f309c5f92c
7 changed files with 117 additions and 57 deletions

View file

@ -17,6 +17,9 @@ module Language.Java.Classfile (Classfile(..)) where
import GHC.Generics (Generic, Generically(Generically)) import GHC.Generics (Generic, Generically(Generically))
import Data.Kind (Type) import Data.Kind (Type)
import Data.Word (Word16)
import Pretty.Serialize (PrettySerialize)
import Language.Java.Classfile.Stage (Stage(Parse)) import Language.Java.Classfile.Stage (Stage(Parse))
import Language.Java.Classfile.Version (Version) import Language.Java.Classfile.Version (Version)
@ -24,13 +27,11 @@ import Language.Java.Classfile.Magic (Magic)
import Language.Java.Classfile.Extractable (Extractable) import Language.Java.Classfile.Extractable (Extractable)
import Language.Java.Classfile.ConstantPool (ConstantPool) import Language.Java.Classfile.ConstantPool (ConstantPool)
import Language.Java.Classfile.Flags (Flags, FlagMask (..)) import Language.Java.Classfile.Flags (Flags, FlagMask (..))
import Language.Java.Classfile.ConstantPool.References (Class) import Language.Java.Classfile.ConstantPool.References (Class, Utf8)
import Language.Java.Classfile.Interfaces (Interfaces) import Language.Java.Classfile.Interfaces (Interfaces)
import Language.Java.Classfile.Fields (Fields) import Language.Java.Classfile.Fields (Fields)
import Language.Java.Classfile.Methods (Methods) import Language.Java.Classfile.Methods (Methods)
import Language.Java.Classfile.Attributes (Attributes) import Language.Java.Classfile.Attributes (Attributes, Attribute)
import Data.Word (Word16)
import Pretty.Serialize (PrettySerialize)
-- | 'Stage'-indexed classfile. It can represent a class, an interface or a module. -- | 'Stage'-indexed classfile. It can represent a class, an interface or a module.
@ -43,14 +44,14 @@ data Classfile stage = Classfile
, accessFlags :: ClassFlags stage , accessFlags :: ClassFlags stage
, this :: Class stage , this :: Class stage
, super :: Class stage , super :: Class stage
, interfaces :: Interfaces , interfaces :: Interfaces stage
, fields :: Fields , fields :: Fields stage
, methods :: Methods , methods :: Methods stage
, attributes :: Attributes , attributes :: Attributes stage
} }
deriving stock (Generic) deriving stock (Generic)
deriving instance (Show (Magic stage), Show (ConstantPool stage), Show (ClassFlags stage), Show (Class stage)) => Show (Classfile stage) deriving instance (Show (Attribute stage), Show (Utf8 stage), Show (Magic stage), Show (ConstantPool stage), Show (ClassFlags stage), Show (Class stage)) => Show (Classfile stage)
deriving via Generically (Classfile Parse) instance (Extractable (Classfile Parse)) deriving via Generically (Classfile Parse) instance (Extractable (Classfile Parse))
deriving via Generically (Classfile Parse) instance (PrettySerialize (Classfile Parse)) deriving via Generically (Classfile Parse) instance (PrettySerialize (Classfile Parse))

View file

@ -3,28 +3,43 @@
{-# LANGUAGE GeneralizedNewtypeDeriving #-} {-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE DerivingVia #-} {-# LANGUAGE DerivingVia #-}
{-# LANGUAGE DeriveGeneric #-} {-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE StandaloneKindSignatures #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE UndecidableInstances #-}
module Language.Java.Classfile.Attributes (Attributes(..), Attribute(..)) where module Language.Java.Classfile.Attributes (Attributes(..), Attribute(..)) where
import Data.Array.IArray (Array) import Data.Array.IArray (Array)
import Data.Word (Word16, Word32) import Data.Word (Word16, Word32)
import Language.Java.Classfile.Extractable (Extractable) import Language.Java.Classfile.Extractable (Extractable)
import Language.Java.Classfile.ConstantPool.References (Utf8Reference) import Language.Java.Classfile.ConstantPool.References (Utf8)
import Language.Java.Classfile.Extractable.SizedBytes (SizedBytes) import Language.Java.Classfile.Extractable.SizedBytes (SizedBytes)
import GHC.Generics ( Generic, Generically(..) ) import GHC.Generics ( Generic, Generically(..) )
import Pretty.Serialize (PrettySerialize) import Pretty.Serialize (PrettySerialize)
import Language.Java.Classfile.Stage (Stage(Parse))
import Data.Kind (Type)
import Data.Typeable (Typeable)
-- | Generic Attribute array used everywhere. -- | Generic Attribute array used everywhere.
-- --
-- Will not respect Attribute location restrictions, does not attempt to parse anything specific. -- Will not respect Attribute location restrictions, does not attempt to parse anything specific.
newtype Attributes = Attributes (Array Word16 Attribute) type Attributes :: Stage -> Type
deriving stock (Show) newtype Attributes stage = Attributes (Array Word16 (Attribute stage))
deriving newtype (Extractable, PrettySerialize)
deriving stock instance Show (Attribute stage) => Show (Attributes stage)
deriving newtype instance (Extractable (Attribute stage), Typeable stage) => Extractable (Attributes stage)
deriving newtype instance (PrettySerialize (Attribute stage), Typeable stage) => PrettySerialize (Attributes stage)
-- | Unknown Attribute -- | Unknown Attribute
data Attribute = Attribute type Attribute :: Stage -> Type
{ name :: Utf8Reference data family Attribute stage
data instance Attribute Parse = RawAttribute
{ name :: Utf8 Parse
, info :: SizedBytes Word32 , info :: SizedBytes Word32
} }
deriving stock (Show, Generic) deriving stock (Show, Generic)
deriving (Extractable, PrettySerialize) via Generically Attribute deriving (Extractable, PrettySerialize) via Generically (Attribute Parse)

View file

@ -11,9 +11,10 @@
{-# LANGUAGE GeneralizedNewtypeDeriving #-} {-# LANGUAGE GeneralizedNewtypeDeriving #-}
module Language.Java.Classfile.ConstantPool.Entry (Entry(..), StorageCount(..), storageCount, MethodHandleInfo(..)) where module Language.Java.Classfile.ConstantPool.Entry (Entry(..), StorageCount(..), storageCount, MethodHandleInfo(..)) where
import GHC.Generics (Generic, Generically(..)) import GHC.Generics (Generic, Generically(..))
import Language.Java.Classfile.Stage (Stage(Parse))
import Language.Java.Classfile.Extractable (Extractable (extract)) import Language.Java.Classfile.Extractable (Extractable (extract))
import Language.Java.Classfile.Extractable.WithTag (Word8Tag) import Language.Java.Classfile.Extractable.WithTag (Word8Tag)
import Language.Java.Classfile.ConstantPool.References (ClassReference, NameAndTypeReference, MethodHandleReferenceKind, OpaqueReference, BootstrapMethodIndex, Utf8Reference) import Language.Java.Classfile.ConstantPool.References (Class, NameAndTypeReference, MethodHandleReferenceKind, OpaqueReference, BootstrapMethodIndex, Utf8)
import Data.Int (Int32, Int64) import Data.Int (Int32, Int64)
import Data.Word (Word16) import Data.Word (Word16)
import Data.Text (Text) import Data.Text (Text)
@ -36,29 +37,29 @@ data Entry
-- ^ Constant value for ldc -- ^ Constant value for ldc
| Double (Word8Tag 6 Double) | Double (Word8Tag 6 Double)
-- ^ Constant value for ldc -- ^ Constant value for ldc
| Class (Word8Tag 7 Utf8Reference) | Class (Word8Tag 7 (Utf8 Parse))
-- ^ Reference to another class: full name -- ^ Reference to another class: full name
| String (Word8Tag 8 Utf8Reference) | String (Word8Tag 8 (Utf8 Parse))
-- ^ Constant value for ldc or ConstantValue attributes. -- ^ Constant value for ldc or ConstantValue attributes.
| FieldRef (Word8Tag 9 (ClassReference, NameAndTypeReference)) | FieldRef (Word8Tag 9 (Class Parse, NameAndTypeReference))
-- ^ Reference to a field: (containing class, descriptor) -- ^ Reference to a field: (containing class, descriptor)
| MethodRef (Word8Tag 10 (ClassReference, NameAndTypeReference)) | MethodRef (Word8Tag 10 (Class Parse, NameAndTypeReference))
-- ^ Reference to a method: (containing class, descriptor) -- ^ Reference to a method: (containing class, descriptor)
| InterfaceMethodRef (Word8Tag 11 (ClassReference, NameAndTypeReference)) | InterfaceMethodRef (Word8Tag 11 (Class Parse, NameAndTypeReference))
-- ^ Reference to an interface method: (containing class, descriptor) -- ^ Reference to an interface method: (containing class, descriptor)
| NameAndType (Word8Tag 12 (Utf8Reference, Utf8Reference)) | NameAndType (Word8Tag 12 (Utf8 Parse, Utf8 Parse))
-- ^ Name and Type: (name, type) -- ^ Name and Type: (name, type)
| MethodHandle (Word8Tag 15 MethodHandleInfo) | MethodHandle (Word8Tag 15 MethodHandleInfo)
-- ^ Reference to a Method, but more *dynamic* -- ^ Reference to a Method, but more *dynamic*
| MethodType (Word8Tag 16 Utf8Reference) | MethodType (Word8Tag 16 (Utf8 Parse))
-- ^ Descriptor of a Method -- ^ Descriptor of a Method
| Dynamic (Word8Tag 17 (BootstrapMethodIndex, NameAndTypeReference)) | Dynamic (Word8Tag 17 (BootstrapMethodIndex, NameAndTypeReference))
-- ^ Unspeakable horrors: index into the bootstrapmethod attribute array, NameAndType must refer to a field -- ^ Unspeakable horrors: index into the bootstrapmethod attribute array, NameAndType must refer to a field
| InvokeDynamic (Word8Tag 18 (BootstrapMethodIndex, NameAndTypeReference)) | InvokeDynamic (Word8Tag 18 (BootstrapMethodIndex, NameAndTypeReference))
-- ^ Unspeakable horrors: index into the bootstrapmethod attribute array, NameAndType must refer to a method -- ^ Unspeakable horrors: index into the bootstrapmethod attribute array, NameAndType must refer to a method
| Module (Word8Tag 19 Utf8Reference) | Module (Word8Tag 19 (Utf8 Parse))
-- ^ Some module description -- ^ Some module description
| Package (Word8Tag 20 Utf8Reference) | Package (Word8Tag 20 (Utf8 Parse))
-- ^ Some package description -- ^ Some package description
deriving stock (Show, Generic) deriving stock (Show, Generic)
deriving Extractable via Generically Entry deriving Extractable via Generically Entry

View file

@ -8,7 +8,7 @@
{-# LANGUAGE LambdaCase #-} {-# LANGUAGE LambdaCase #-}
{-# LANGUAGE StandaloneKindSignatures #-} {-# LANGUAGE StandaloneKindSignatures #-}
{-# LANGUAGE DeriveGeneric #-} {-# LANGUAGE DeriveGeneric #-}
module Language.Java.Classfile.ConstantPool.References (Utf8Reference(..), ClassReference(..), NameAndTypeReference(..), MethodHandleReferenceKind(..), OpaqueReference(..), BootstrapMethodIndex(..), Class) where module Language.Java.Classfile.ConstantPool.References (Utf8(..), Class(..), NameAndTypeReference(..), MethodHandleReferenceKind(..), OpaqueReference(..), BootstrapMethodIndex(..), ) where
import Data.Word (Word16, Word8) import Data.Word (Word16, Word8)
import Language.Java.Classfile.Extractable (Extractable) import Language.Java.Classfile.Extractable (Extractable)
import Language.Java.Classfile.Extractable.AsTag import Language.Java.Classfile.Extractable.AsTag
@ -20,23 +20,25 @@ import GHC.Generics (Generically(..), Generic)
-- | Wrapper for constant-pool reference to text. -- | Wrapper for constant-pool reference to text.
newtype Utf8Reference = Utf8Reference Word16 type Utf8 :: Stage -> Type
data family Utf8 stage
newtype instance Utf8 Parse = Utf8Reference Word16
deriving stock (Show, Generic) deriving stock (Show, Generic)
deriving newtype Extractable deriving newtype Extractable
deriving PrettySerialize via Generically Utf8Reference deriving PrettySerialize via Generically (Utf8 Parse)
-- | 'Stage'-indexed type, either a Class or only a t'ClassReference'. -- | 'Stage'-indexed type, either a Class or only a t'ClassReference'.
type Class :: Stage -> Type type Class :: Stage -> Type
type family Class stage where data family Class stage
Class Parse = ClassReference
-- | Reference to a class in a constant-pool. This will resolve into a class. -- | Reference to a class in a constant-pool. This will resolve into a class.
newtype ClassReference = ClassReference Word16 newtype instance Class Parse = ClassReference Word16
deriving stock (Show, Generic) deriving stock (Show, Generic)
deriving newtype Extractable deriving newtype Extractable
deriving PrettySerialize via Generically ClassReference deriving PrettySerialize via Generically (Class Parse)
-- | Reference to a class in a constant-pool. This will resolve to Name and Type. -- | Reference to a class in a constant-pool. This will resolve to Name and Type.

View file

@ -6,21 +6,32 @@
{-# LANGUAGE TypeFamilies #-} {-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE InstanceSigs #-} {-# LANGUAGE InstanceSigs #-}
{-# LANGUAGE LambdaCase #-} {-# LANGUAGE LambdaCase #-}
{-# LANGUAGE StandaloneKindSignatures #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE UndecidableInstances #-}
module Language.Java.Classfile.Fields (Fields(..)) where module Language.Java.Classfile.Fields (Fields(..)) where
import Data.Array.IArray (Array) import Data.Array.IArray (Array)
import Data.Word (Word16) import Data.Word (Word16)
import Language.Java.Classfile.Extractable (Extractable) import Language.Java.Classfile.Extractable (Extractable)
import GHC.Generics ( Generically, Generic, Generically(..) ) import GHC.Generics ( Generically, Generic, Generically(..) )
import Language.Java.Classfile.Flags (Flags, FlagMask (..)) import Language.Java.Classfile.Flags (Flags, FlagMask (..))
import Language.Java.Classfile.ConstantPool.References (Utf8Reference) import Language.Java.Classfile.ConstantPool.References (Utf8)
import Language.Java.Classfile.Attributes (Attributes) import Language.Java.Classfile.Attributes (Attributes)
import Pretty.Serialize (PrettySerialize) import Pretty.Serialize (PrettySerialize)
import Language.Java.Classfile.Stage (Stage)
import Data.Kind (Type)
import Data.Typeable (Typeable)
-- | Word16-Array of Fields. -- | Word16-Array of Fields.
newtype Fields = Fields (Array Word16 Field) type Fields :: Stage -> Type
deriving stock Show newtype Fields stage = Fields (Array Word16 (Field stage))
deriving newtype (Extractable, PrettySerialize)
deriving stock instance (Show (Field stage)) => Show (Fields stage)
deriving newtype instance (Typeable stage, Extractable (Utf8 stage), Extractable (Attributes stage)) => Extractable (Fields stage)
deriving newtype instance (Typeable stage, PrettySerialize (Utf8 stage), PrettySerialize (Attributes stage)) => PrettySerialize (Fields stage)
-- | All the access flags a field can have -- | All the access flags a field can have
@ -53,11 +64,15 @@ instance FlagMask FieldFlag where
-- | A singular field of a class. -- | A singular field of a class.
data Field = Field type Field :: Stage -> Type
data Field stage = Field
{ flags :: Flags FieldFlag { flags :: Flags FieldFlag
, name :: Utf8Reference , name :: Utf8 stage
, descriptor :: Utf8Reference , descriptor :: Utf8 stage
, attribute :: Attributes , attribute :: Attributes stage
} }
deriving stock (Show, Generic) deriving stock (Generic)
deriving (Extractable, PrettySerialize) via Generically Field
deriving stock instance (Show (Utf8 stage), Show (Attributes stage)) => Show (Field stage)
deriving via Generically (Field stage) instance (Extractable (Utf8 stage), Extractable (Attributes stage)) => Extractable (Field stage)
deriving via Generically (Field stage) instance (PrettySerialize (Utf8 stage), PrettySerialize (Attributes stage)) => PrettySerialize (Field stage)

View file

@ -2,16 +2,28 @@
{-# LANGUAGE DeriveGeneric #-} {-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DerivingVia #-} {-# LANGUAGE DerivingVia #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE StandaloneKindSignatures #-}
{-# LANGUAGE DataKinds #-}
module Language.Java.Classfile.Interfaces (Interfaces(..)) where module Language.Java.Classfile.Interfaces (Interfaces(..)) where
import Data.Array.IArray (Array) import Data.Array.IArray (Array)
import Data.Word (Word16) import Data.Word (Word16)
import Language.Java.Classfile.ConstantPool.References (ClassReference) import Language.Java.Classfile.ConstantPool.References (Class)
import Language.Java.Classfile.Extractable (Extractable) import Language.Java.Classfile.Extractable (Extractable)
import GHC.Generics ( Generic, Generically, Generically(..) ) import GHC.Generics ( Generic, Generically, Generically(..) )
import Pretty.Serialize (PrettySerialize) import Pretty.Serialize (PrettySerialize)
import Language.Java.Classfile.Stage (Stage)
import Data.Kind (Type)
import Data.Typeable (Typeable)
-- | A list of classes something implements. -- | A list of classes something implements.
newtype Interfaces = Interfaces (Array Word16 ClassReference) type Interfaces :: Stage -> Type
deriving stock (Show, Generic) newtype Interfaces stage = Interfaces (Array Word16 (Class stage))
deriving (Extractable, PrettySerialize) via Generically Interfaces deriving stock (Generic)
deriving stock instance (Show (Class stage)) => Show (Interfaces stage)
deriving via Generically (Interfaces stage) instance (Extractable (Class stage), Typeable stage) => Extractable (Interfaces stage)
deriving via Generically (Interfaces stage) instance (PrettySerialize (Class stage), Typeable stage) => PrettySerialize (Interfaces stage)

View file

@ -6,32 +6,46 @@
{-# LANGUAGE InstanceSigs #-} {-# LANGUAGE InstanceSigs #-}
{-# LANGUAGE LambdaCase #-} {-# LANGUAGE LambdaCase #-}
{-# LANGUAGE TypeFamilies #-} {-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE StandaloneKindSignatures #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE UndecidableInstances #-}
module Language.Java.Classfile.Methods (Methods(..), Method(..), MethodFlag(..)) where module Language.Java.Classfile.Methods (Methods(..), Method(..), MethodFlag(..)) where
import Data.Array.IArray (Array) import Data.Array.IArray (Array)
import Data.Word (Word16) import Data.Word (Word16)
import Language.Java.Classfile.Flags (Flags, FlagMask (..)) import Language.Java.Classfile.Flags (Flags, FlagMask (..))
import Language.Java.Classfile.Extractable (Extractable) import Language.Java.Classfile.Extractable (Extractable)
import GHC.Generics ( Generically, Generic, Generically(..) ) import GHC.Generics ( Generically, Generic, Generically(..) )
import Language.Java.Classfile.ConstantPool.References (Utf8Reference) import Language.Java.Classfile.ConstantPool.References (Utf8)
import Language.Java.Classfile.Attributes (Attributes) import Language.Java.Classfile.Attributes (Attributes)
import Pretty.Serialize (PrettySerialize) import Pretty.Serialize (PrettySerialize)
import Language.Java.Classfile.Stage (Stage)
import Data.Kind (Type)
import Data.Typeable (Typeable)
-- | Alias for the methods structure from the constant-pool. -- | Alias for the methods structure from the constant-pool.
newtype Methods = Methods (Array Word16 Method) newtype Methods stage = Methods (Array Word16 (Method stage))
deriving stock (Show)
deriving newtype (Extractable, PrettySerialize) deriving stock instance (Show (Utf8 stage), Show (Attributes stage)) => Show (Methods stage)
deriving newtype instance (Typeable stage, Extractable (Utf8 stage), Extractable (Attributes stage)) => Extractable (Methods stage)
deriving newtype instance (Typeable stage, PrettySerialize (Utf8 stage), PrettySerialize (Attributes stage)) => PrettySerialize (Methods stage)
-- | A single method record, contains attributes, name and access flags. -- | A single method record, contains attributes, name and access flags.
data Method = Method type Method :: Stage -> Type
data Method stage = Method
{ flags :: Flags MethodFlag { flags :: Flags MethodFlag
, name :: Utf8Reference , name :: Utf8 stage
, descriptor :: Utf8Reference , descriptor :: Utf8 stage
, attributes :: Attributes , attributes :: Attributes stage
} }
deriving stock (Show, Generic) deriving stock (Generic)
deriving (Extractable, PrettySerialize) via Generically Method
deriving stock instance (Show (Utf8 stage), Show (Attributes stage)) => Show (Method stage)
deriving via Generically (Method stage) instance (Extractable (Utf8 stage), Extractable (Attributes stage)) => Extractable (Method stage)
deriving via Generically (Method stage) instance (PrettySerialize (Utf8 stage), PrettySerialize (Attributes stage)) => PrettySerialize (Method stage)
-- | Flags for the method, such as abstract, public or static. -- | Flags for the method, such as abstract, public or static.