feat: entire constant pool
This commit is contained in:
parent
f504462d3c
commit
5f3e7b761e
5 changed files with 84 additions and 14 deletions
|
@ -1,15 +1,33 @@
|
|||
{-# LANGUAGE DerivingVia #-}
|
||||
{-# LANGUAGE DeriveGeneric #-}
|
||||
{-# LANGUAGE DataKinds #-}
|
||||
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
|
||||
module Language.Java.Classfile.ConstantPool.Entry (Entry(..)) where
|
||||
import GHC.Generics (Generic, Generically(..))
|
||||
import Language.Java.Classfile.Extractable (Extractable)
|
||||
import Language.Java.Classfile.Extractable.WithTag (Word8Tag)
|
||||
import Language.Java.Classfile.ConstantPool.References (Utf8Reference, ClassReference, NameAndTypeReference)
|
||||
import Language.Java.Classfile.ConstantPool.References (Utf8Reference, ClassReference, NameAndTypeReference, MethodHandleReferenceKind, OpaqueReference, BootstrapMethodIndex)
|
||||
import Data.Int (Int32, Int64)
|
||||
|
||||
data Entry
|
||||
= Class (Word8Tag 7 Utf8Reference) -- name
|
||||
| FieldRef (Word8Tag 9 (ClassReference, NameAndTypeReference))
|
||||
= Integer (Word8Tag 3 Int32)
|
||||
| Float (Word8Tag 4 Float)
|
||||
| Long (Word8Tag 5 Int64)
|
||||
| Double (Word8Tag 6 Double)
|
||||
| Class (Word8Tag 7 Utf8Reference) -- name
|
||||
| String (Word8Tag 8 Utf8Reference) -- value
|
||||
| FieldRef (Word8Tag 9 (ClassReference, NameAndTypeReference)) -- containing class, descriptor
|
||||
| MethodRef (Word8Tag 10 (ClassReference, NameAndTypeReference)) -- containing class, descriptor
|
||||
| InterfaceMethodRef (Word8Tag 11 (ClassReference, NameAndTypeReference)) -- containing class, descriptor
|
||||
| NameAndType (Word8Tag 12 (Utf8Reference, Utf8Reference)) -- name, type
|
||||
| MethodHandle (Word8Tag 15 MethodHandleInfo)
|
||||
| MethodType (Word8Tag 16 Utf8Reference) -- descriptor
|
||||
| Dynamic (Word8Tag 17 (BootstrapMethodIndex, NameAndTypeReference)) -- index into the bootstrapmethod attribute array, NameAndType must refer to a field
|
||||
| InvokeDynamic (Word8Tag 18 (BootstrapMethodIndex, NameAndTypeReference)) -- index into the bootstrapmethod attribute array, NameAndType must refer to a method
|
||||
| Module (Word8Tag 19 Utf8Reference)
|
||||
| Package (Word8Tag 20 Utf8Reference)
|
||||
deriving stock (Show, Generic)
|
||||
deriving Extractable via Generically Entry
|
||||
|
||||
data MethodHandleInfo = MethodHandleInfo MethodHandleReferenceKind OpaqueReference
|
||||
deriving stock (Show, Generic)
|
||||
deriving Extractable via Generically MethodHandleInfo
|
||||
|
|
|
@ -1,8 +1,12 @@
|
|||
{-# LANGUAGE DerivingStrategies #-}
|
||||
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
|
||||
module Language.Java.Classfile.ConstantPool.References (Utf8Reference(..), ClassReference(..), NameAndTypeReference(..)) where
|
||||
{-# LANGUAGE DataKinds #-}
|
||||
{-# LANGUAGE DerivingVia #-}
|
||||
{-# LANGUAGE DeriveGeneric #-}
|
||||
module Language.Java.Classfile.ConstantPool.References (Utf8Reference(..), ClassReference(..), NameAndTypeReference(..), MethodHandleReferenceKind(..), OpaqueReference(..), BootstrapMethodIndex(..)) where
|
||||
import Data.Word (Word16)
|
||||
import Language.Java.Classfile.Extractable (Extractable)
|
||||
import Language.Java.Classfile.Extractable.WithTag (Word8Tag)
|
||||
import GHC.Generics (Generically(..), Generic)
|
||||
|
||||
newtype Utf8Reference = Utf8Reference Word16
|
||||
deriving stock (Show)
|
||||
|
@ -15,3 +19,24 @@ newtype ClassReference = ClassReference Word16
|
|||
newtype NameAndTypeReference = NameAndTypeReference Word16
|
||||
deriving stock (Show)
|
||||
deriving newtype Extractable
|
||||
|
||||
newtype OpaqueReference = OpaqueReference Word16
|
||||
deriving stock (Show)
|
||||
deriving newtype Extractable
|
||||
|
||||
newtype BootstrapMethodIndex = BootstrapMethodIndex Word16
|
||||
deriving stock (Show)
|
||||
deriving newtype Extractable
|
||||
|
||||
data MethodHandleReferenceKind
|
||||
= GetField (Word8Tag 1 ()) -- I kind of want to redo this
|
||||
| GetStatic (Word8Tag 2 ())
|
||||
| PutField (Word8Tag 3 ())
|
||||
| PutStatic (Word8Tag 4 ())
|
||||
| InvokeVirtual (Word8Tag 5 ())
|
||||
| InvokeStatic (Word8Tag 6 ())
|
||||
| InvokeSpecial (Word8Tag 7 ())
|
||||
| NewInvokeSpecial (Word8Tag 8 ())
|
||||
| InvokeInterface (Word8Tag 9 ())
|
||||
deriving stock (Show, Generic)
|
||||
deriving Extractable via Generically MethodHandleReferenceKind
|
||||
|
|
|
@ -2,6 +2,9 @@
|
|||
{-# LANGUAGE TypeOperators #-}
|
||||
{-# LANGUAGE FlexibleContexts #-}
|
||||
{-# LANGUAGE UndecidableInstances #-}
|
||||
{-# LANGUAGE TypeApplications #-}
|
||||
{-# LANGUAGE StandaloneDeriving #-}
|
||||
{-# LANGUAGE DerivingVia #-}
|
||||
module Language.Java.Classfile.Extractable (Extractable(extract), expectConstant) where
|
||||
|
||||
import Language.Java.Classfile.Extract (Extract, bytes, expectEqual)
|
||||
|
@ -10,9 +13,12 @@ import qualified Data.ByteString.Lazy as ByteString
|
|||
import Data.ByteString.Lazy (ByteString)
|
||||
import Data.Bits (Bits(shiftL, (.|.)))
|
||||
import GHC.Generics (U1 (U1), (:*:) ((:*:)), (:+:) (L1, R1), M1 (M1), K1 (K1), Generic (Rep, to), Generically (Generically))
|
||||
import Control.Applicative ((<|>), empty)
|
||||
import Control.Applicative ((<|>))
|
||||
import Data.Array.IArray (Array, listArray, Ix)
|
||||
import Control.Monad (replicateM)
|
||||
import Data.Int (Int32, Int64)
|
||||
import Language.Java.Classfile.FromBigEndian (FromBigEndian(fromBigEndian))
|
||||
import GHC.Float (castWord32ToFloat, castWord64ToDouble)
|
||||
|
||||
class Extractable a where
|
||||
extract :: Extract a
|
||||
|
@ -23,11 +29,31 @@ instance Extractable Word8 where
|
|||
|
||||
instance Extractable Word16 where
|
||||
extract :: Extract Word16
|
||||
extract = build <$> bytes 2
|
||||
extract = fromBigEndian . build <$> bytes 2
|
||||
|
||||
instance Extractable Word32 where
|
||||
extract :: Extract Word32
|
||||
extract = build <$> bytes 4
|
||||
extract = fromBigEndian . build <$> bytes 4
|
||||
|
||||
instance Extractable Int32 where
|
||||
extract :: Extract Int32
|
||||
extract = fromIntegral <$> extract @Word32
|
||||
|
||||
instance Extractable Float where
|
||||
extract :: Extract Float
|
||||
extract = castWord32ToFloat <$> extract
|
||||
|
||||
instance Extractable Double where
|
||||
extract :: Extract Double
|
||||
extract = castWord64ToDouble . build <$> bytes 8
|
||||
|
||||
instance Extractable Int64 where
|
||||
extract :: Extract Int64
|
||||
extract = do
|
||||
high <- extract @Word32
|
||||
low <- extract @Word32
|
||||
|
||||
pure $ (fromIntegral high `shiftL` 32) .|. fromIntegral low
|
||||
|
||||
instance (Extractable index, Extractable element, Ix index, Integral index) => Extractable (Array index element) where
|
||||
extract :: Extract (Array index element)
|
||||
|
@ -36,9 +62,9 @@ instance (Extractable index, Extractable element, Ix index, Integral index) => E
|
|||
elements <- replicateM (fromIntegral count) extract
|
||||
pure $ listArray (1, count) elements
|
||||
|
||||
instance (Extractable a, Extractable b) => Extractable (a, b) where
|
||||
extract :: Extract (a, b)
|
||||
extract = (,) <$> extract <*> extract
|
||||
deriving via Generically () instance Extractable ()
|
||||
deriving via Generically (a, b) instance (Extractable a, Extractable b) => Extractable (a, b)
|
||||
deriving via Generically (a, b, c) instance (Extractable a, Extractable b, Extractable c) => Extractable (a, b, c)
|
||||
|
||||
expectConstant :: (Extractable a, Eq a) => a -> Extract a
|
||||
expectConstant = expectEqual extract
|
||||
|
|
|
@ -5,7 +5,7 @@
|
|||
{-# LANGUAGE TypeApplications #-}
|
||||
{-# LANGUAGE ScopedTypeVariables #-}
|
||||
{-# LANGUAGE DataKinds #-}
|
||||
module Language.Java.Classfile.Extractable.WithTag where
|
||||
module Language.Java.Classfile.Extractable.WithTag (Word8Tag, WithNumericTag(..)) where
|
||||
import Language.Java.Classfile.Extractable (Extractable (extract), expectConstant)
|
||||
import Language.Java.Classfile.Extract (Extract)
|
||||
import GHC.TypeLits (Natural, natVal, KnownNat)
|
||||
|
|
|
@ -1,8 +1,9 @@
|
|||
{-# LANGUAGE InstanceSigs #-}
|
||||
module Language.Java.Classfile.FromBigEndian () where
|
||||
module Language.Java.Classfile.FromBigEndian (FromBigEndian(fromBigEndian)) where
|
||||
import Data.Word (Word16, byteSwap16, Word32, byteSwap32)
|
||||
import GHC.ByteOrder (ByteOrder(..))
|
||||
import qualified GHC.ByteOrder as GHC
|
||||
import Data.Int (Int32)
|
||||
|
||||
class FromBigEndian a where
|
||||
fromBigEndian :: a -> a
|
||||
|
|
Loading…
Add table
Add a link
Reference in a new issue