hs-java-0.3.4: Java .class files assembler/disassembler

Safe HaskellNone

JVM.ClassFile

Contents

Description

This module declares (low-level) data types for Java .class files structures, and Binary instances to read/write them.

Synopsis

About

Java .class file uses constants pool, which stores almost all source-code-level constants (strings, integer literals etc), and also all identifiers (class, method, field names etc). All other structures contain indexes of constants in the pool instead of constants theirself.

It's not convient to use that indexes programmatically. So, .class file is represented at two stages: File and Direct. At File stage, all data structures contain only indexes, not constants theirself. When we read a class from a file, we get structure at File stage. We only can write File stage structure to file.

At Direct stage, structures conain constants, not indexes. Convertion functions (File - Direct) are located in the JVM.Converter module.

data Attribute Source

Any (class field method/ ...) attribute format. Some formats specify special formats for attributeValue.

Constructors

Attribute 

Fields

attributeName :: Word16
 
attributeLength :: Word32
 
attributeValue :: ByteString
 

Instances

Eq Attribute 
Show Attribute 
Binary Attribute 
BinaryState Integer Attribute 

data FieldType Source

Field signature format

Constructors

SignedByte

B

CharByte

C

DoubleType

D

FloatType

F

IntType

I

LongInt

J

ShortInt

S

BoolType

Z

ObjectType String

L {class name}

Array (Maybe Int) FieldType
[{type}

Instances

Eq FieldType 
Ord FieldType 
Show FieldType 
Binary FieldType 

Signatures

type FieldSignature = FieldTypeSource

Class field signature

data MethodSignature Source

Class method argument signature

data ReturnSignature Source

Return value signature

type ArgumentSignature = FieldTypeSource

Method argument signature

Stage types

data File Source

File stage

Instances

Eq (Method File) 
Eq (Field File) 
Eq (Class File) 
Eq (Constant File) 
Eq (Attributes File) 
Show (Method File) 
Show (Field File) 
Show (Class File) 
Show (Constant File) 
Show (Attributes File) 
Default (Attributes File) 
Binary (Method File) 
Binary (Field File) 
Binary (Class File) 

data Direct Source

Direct representation stage

Staged structures

type Pool stage = Map Word16 (Constant stage)Source

Constant pool

type family Link stage a Source

Link to some object

data Method stage Source

Class method format

Instances

data Field stage Source

Class field format

Instances

data Class stage Source

Generic .class file format

Constructors

Class 

Fields

magic :: Word32

Magic value: 0xCAFEBABE

minorVersion :: Word16
 
majorVersion :: Word16
 
constsPoolSize :: Word16

Number of items in constants pool

constsPool :: Pool stage

Constants pool itself

accessFlags :: AccessFlags stage

See JVM.Types.AccessFlag

thisClass :: Link stage ByteString

Constants pool item index for this class

superClass :: Link stage ByteString
  • -/-- for super class, zero for java.lang.Object
interfacesCount :: Word16

Number of implemented interfaces

interfaces :: [Link stage ByteString]

Constants pool item indexes for implemented interfaces

classFieldsCount :: Word16

Number of class fileds

classFields :: [Field stage]

Class fields

classMethodsCount :: Word16

Number of class methods

classMethods :: [Method stage]

Class methods

classAttributesCount :: Word16

Number of class attributes

classAttributes :: Attributes stage

Class attributes

Instances

HasAttributes Class 
Eq (Class Direct) 
Eq (Class File) 
Show (Class Direct) 
Show (Class File) 
Binary (Class File) 

data Constant stage Source

Constant pool item

Constructors

CClass (Link stage ByteString) 
CField (Link stage ByteString) (Link stage (NameType (Field stage))) 
CMethod (Link stage ByteString) (Link stage (NameType (Method stage))) 
CIfaceMethod (Link stage ByteString) (Link stage (NameType (Method stage))) 
CString (Link stage ByteString) 
CInteger Word32 
CFloat Float 
CLong Word64 
CDouble Double 
CNameType (Link stage ByteString) (Link stage ByteString) 
CUTF8 
CUnicode 

Instances

Eq (Constant Direct) 
Eq (Constant File) 
Show (Constant Direct) 
Show (Constant File) 

data AccessFlag Source

Access flags. Used for classess, methods, variables.

Constructors

ACC_PUBLIC

0x0001 Visible for all

ACC_PRIVATE

0x0002 Visible only for defined class

ACC_PROTECTED

0x0004 Visible only for subclasses

ACC_STATIC

0x0008 Static method or variable

ACC_FINAL

0x0010 No further subclassing or assignments

ACC_SYNCHRONIZED

0x0020 Uses monitors

ACC_VOLATILE

0x0040 Could not be cached

ACC_TRANSIENT

0x0080

ACC_NATIVE

0x0100 Implemented in other language

ACC_INTERFACE

0x0200 Class is interface

ACC_ABSTRACT

0x0400

Instances

type family AccessFlags stage Source

Object (class, method, field …) access flags

data family Attributes stage Source

Object (class, method, field) attributes

defaultClass :: (Default (AccessFlags stage), Default (Link stage ByteString), Default (Attributes stage)) => Class stageSource

Default (empty) class file definition.

Misc

class (Binary (Signature a), Show (Signature a), Eq (Signature a)) => HasSignature a Source

Fields and methods have signatures.

Associated Types

type Signature a Source

data NameType a Source

Name and signature pair. Used for methods and fields.

Constructors

NameType 

Instances

HasSignature a => Eq (NameType a) 
HasSignature a => Show (NameType a) 
HasSignature a => Binary (NameType a) 

long :: Constant stage -> BoolSource

className :: Constant Direct -> ByteStringSource

Name of the CClass. Error on any other constant.

apsize :: Attributes File -> IntSource

Size of attributes set at File stage

arsize :: Attributes Direct -> IntSource

Size of attributes set at Direct stage

arlist :: Attributes Direct -> [(ByteString, ByteString)]Source

Associative list of attributes at Direct stage