Copyright | (c) Christian Gram Kalhauge 2017 |
---|---|
License | MIT |
Maintainer | kalhuage@cs.ucla.edu |
Safe Haskell | None |
Language | Haskell2010 |
Language.JVM.Constant
Description
This module contains the Constant
type and the ConstantPool
. These
are essential for accessing data in the class-file.
Synopsis
- data Constant r
- = CString !SizedByteString16
- | CInteger !Int32
- | CFloat !Float
- | CLong !Int64
- | CDouble !Double
- | CClassRef !(Ref Text r)
- | CStringRef !(Ref ByteString r)
- | CFieldRef !(Choice (Index, Index) AbsFieldId r)
- | CMethodRef !(Choice (Index, Index) (InRefType MethodId) r)
- | CInterfaceMethodRef !(Choice (Index, Index) (InRefType MethodId) r)
- | CNameAndType !(Ref Text r) !(Ref Text r)
- | CMethodHandle !(MethodHandle r)
- | CMethodType !(Ref MethodDescriptor r)
- | CInvokeDynamic !(InvokeDynamic r)
- constantSize :: Constant r -> Index
- typeToStr :: Constant r -> String
- class Referenceable a where
- data JValue
- type VInteger = Int32
- type VLong = Int64
- type VDouble = Double
- type VFloat = Float
- type VString = ByteString
- data ClassName
- data InClass a = InClass {
- inClassName :: !ClassName
- inClassId :: !a
- data InRefType a = InRefType {
- inRefType :: !JRefType
- inRefTypeId :: !a
- parseAbsMethodId :: Parser AbsMethodId
- newtype AbsFieldId = AbsFieldId {}
- newtype AbsInterfaceMethodId = AbsInterfaceMethodId {}
- data AbsVariableMethodId = AbsVariableMethodId {}
- newtype MethodId = MethodId {}
- newtype FieldId = FieldId {}
- data NameAndType a = NameAndType !Text !a
- data MethodDescriptor
- data FieldDescriptor
- data MethodHandle r
- = MHField !(MethodHandleField r)
- | MHMethod !(MethodHandleMethod r)
- | MHInterface !(MethodHandleInterface r)
- data MethodHandleField r = MethodHandleField {}
- data MethodHandleMethod r
- = MHInvokeVirtual !(Ref (InRefType MethodId) r)
- | MHInvokeStatic !(Ref AbsVariableMethodId r)
- | MHInvokeSpecial !(Ref AbsVariableMethodId r)
- | MHNewInvokeSpecial !(Ref (InRefType MethodId) r)
- newtype MethodHandleInterface r = MethodHandleInterface {}
- data MethodHandleFieldKind
- data InvokeDynamic r = InvokeDynamic {
- invokeDynamicAttrIndex :: !Word16
- invokeDynamicMethod :: !(Ref MethodId r)
- data High
- data Low
Documentation
A constant is a multi word item in the ConstantPool
. Each of
the constructors are pretty much self-explanatory from the types.
Constructors
CString !SizedByteString16 | |
CInteger !Int32 | |
CFloat !Float | |
CLong !Int64 | |
CDouble !Double | |
CClassRef !(Ref Text r) | |
CStringRef !(Ref ByteString r) | |
CFieldRef !(Choice (Index, Index) AbsFieldId r) | |
CMethodRef !(Choice (Index, Index) (InRefType MethodId) r) | |
CInterfaceMethodRef !(Choice (Index, Index) (InRefType MethodId) r) | |
CNameAndType !(Ref Text r) !(Ref Text r) | |
CMethodHandle !(MethodHandle r) | |
CMethodType !(Ref MethodDescriptor r) | |
CInvokeDynamic !(InvokeDynamic r) |
Instances
constantSize :: Constant r -> Index Source #
Some of the Constant
s take up more space in the constant pool than other.
Notice that String
and MethodType
is not of size
32, but is still awarded value 1. This is due to an
inconsistency
in JVM.
class Referenceable a where Source #
Referenceable
is something that can exist in the constant pool.
Instances
JValue
A constant pool value in java
Constructors
VInteger VInteger | |
VLong VLong | |
VFloat VFloat | |
VDouble VDouble | |
VString VString | |
VClass JRefType | |
VMethodType MethodDescriptor | |
VMethodHandle (MethodHandle High) |
Instances
type VString = ByteString Source #
Special constants
A class name
Instances
Eq ClassName Source # | |
Ord ClassName Source # | |
Show ClassName Source # | |
IsString ClassName Source # | |
Defined in Language.JVM.Type Methods fromString :: String -> ClassName # | |
Generic ClassName Source # | |
NFData ClassName Source # | |
Defined in Language.JVM.Type | |
TextSerializable ClassName Source # | |
Referenceable ClassName Source # | |
type Rep ClassName Source # | |
Defined in Language.JVM.Type |
A method or Field in a Class
Constructors
InClass | |
Fields
|
Instances
Eq a => Eq (InClass a) Source # | |
Ord a => Ord (InClass a) Source # | |
Show a => Show (InClass a) Source # | |
Generic (InClass a) Source # | |
NFData a => NFData (InClass a) Source # | |
Defined in Language.JVM.Type | |
type Rep (InClass a) Source # | |
Defined in Language.JVM.Type type Rep (InClass a) = D1 (MetaData "InClass" "Language.JVM.Type" "jvm-binary-0.9.0-9S1OjG3yP2JAIJl8zf6L4B" False) (C1 (MetaCons "InClass" PrefixI True) (S1 (MetaSel (Just "inClassName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 ClassName) :*: S1 (MetaSel (Just "inClassId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 a))) |
A method or Field in a Class
Constructors
InRefType | |
Fields
|
Instances
Eq a => Eq (InRefType a) Source # | |
Ord a => Ord (InRefType a) Source # | |
Defined in Language.JVM.Type | |
Show a => Show (InRefType a) Source # | |
Generic (InRefType a) Source # | |
NFData a => NFData (InRefType a) Source # | |
Defined in Language.JVM.Type | |
Referenceable (InRefType MethodId) Source # | |
type Rep (InRefType a) Source # | |
Defined in Language.JVM.Type type Rep (InRefType a) = D1 (MetaData "InRefType" "Language.JVM.Type" "jvm-binary-0.9.0-9S1OjG3yP2JAIJl8zf6L4B" False) (C1 (MetaCons "InRefType" PrefixI True) (S1 (MetaSel (Just "inRefType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 JRefType) :*: S1 (MetaSel (Just "inRefTypeId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 a))) |
newtype AbsFieldId Source #
A FieldId
Constructors
AbsFieldId | |
Fields |
Instances
newtype AbsInterfaceMethodId Source #
An method which is from an interface
Constructors
AbsInterfaceMethodId | |
Fields |
Instances
data AbsVariableMethodId Source #
An method which can be from an interface
Constructors
AbsVariableMethodId | |
Fields
|
Instances
A MethodId
Constructors
MethodId | |
Instances
A FieldId
Constructors
FieldId | |
Instances
Eq FieldId Source # | |
Ord FieldId Source # | |
Show FieldId Source # | |
IsString FieldId Source # | |
Defined in Language.JVM.Type Methods fromString :: String -> FieldId # | |
Generic FieldId Source # | |
NFData FieldId Source # | |
Defined in Language.JVM.Type | |
TextSerializable FieldId Source # | |
AsNameAndType FieldId Source # | |
Defined in Language.JVM.Type Associated Types type TypeDescriptor FieldId :: Type Source # Methods toNameAndType :: FieldId -> NameAndType (TypeDescriptor FieldId) Source # | |
Referenceable FieldId Source # | |
type Rep FieldId Source # | |
Defined in Language.JVM.Type type Rep FieldId = D1 (MetaData "FieldId" "Language.JVM.Type" "jvm-binary-0.9.0-9S1OjG3yP2JAIJl8zf6L4B" True) (C1 (MetaCons "FieldId" PrefixI True) (S1 (MetaSel (Just "fieldIdAsNameAndType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (NameAndType FieldDescriptor)))) | |
type TypeDescriptor FieldId Source # | |
Defined in Language.JVM.Type |
data NameAndType a Source #
A name and a type
Constructors
NameAndType !Text !a |
Instances
data MethodDescriptor Source #
Method Descriptor
Instances
data FieldDescriptor Source #
Field Descriptor
Instances
data MethodHandle r Source #
The union type over the different method handles.
Constructors
MHField !(MethodHandleField r) | |
MHMethod !(MethodHandleMethod r) | |
MHInterface !(MethodHandleInterface r) |
Instances
data MethodHandleField r Source #
Constructors
MethodHandleField | |
Fields |
Instances
data MethodHandleMethod r Source #
Constructors
MHInvokeVirtual !(Ref (InRefType MethodId) r) | |
MHInvokeStatic !(Ref AbsVariableMethodId r) | Since version 52.0 |
MHInvokeSpecial !(Ref AbsVariableMethodId r) | Since version 52.0 |
MHNewInvokeSpecial !(Ref (InRefType MethodId) r) |
Instances
newtype MethodHandleInterface r Source #
Constructors
MethodHandleInterface | |
Fields |
Instances
data MethodHandleFieldKind Source #
Constructors
MHGetField | |
MHGetStatic | |
MHPutField | |
MHPutStatic |
Instances
data InvokeDynamic r Source #
Constructors
InvokeDynamic | |
Fields
|
Instances
re-exports
Any data structure in the High
stage, is easier to read.
Instances
Any data structure that is in the low stage should be serializable using the binary library.