jvm-parser-0.2.1: A parser for JVM bytecode files

Portabilityportable
Stabilitystable
Maintaineratomb@galois.com
Safe HaskellNone

Language.JVM.Parser

Contents

Description

Parser for the JVM bytecode format.

Synopsis

Basic types

data Type Source

JVM Type

Constructors

ArrayType Type 
BooleanType 
ByteType 
CharType 
ClassType String

ClassType with name of packages separated by slash /

DoubleType 
FloatType 
IntType 
LongType 
ShortType 

Instances

isIValue :: Type -> BoolSource

Returns true if type is an integer value.

isPrimitiveType :: Type -> BoolSource

Returns true if Java type is a primitive type. Primitive types are the Boolean type or numeric types.

isRValue :: Type -> BoolSource

Returns true if type is a reference value.

stackWidth :: Type -> IntSource

Returns number of bits that a Java type is expected to take on the stack. Type should be a primitive type.

isFloatType :: Type -> BoolSource

Returns true if Java type denotes a floating point.

isRefType :: Type -> BoolSource

Returns true if Java type denotes a reference.

data ConstantPoolValue Source

A value stored in the constant pool.

data Attribute Source

An uninterpreted user defined attribute in the class file.

SerDes helpers

Class declarations

data Class Source

A JVM class or interface.

Instances

className :: Class -> StringSource

Returns name of the class

superClass :: Class -> Maybe StringSource

Returns name of the super class of this class or Nothing if this class has no super class.

classIsPublic :: Class -> BoolSource

Returns true if class is public.

classIsFinal :: Class -> BoolSource

Returns true if class is final.

classIsInterface :: Class -> BoolSource

Returns true if class is an interface

classIsAbstract :: Class -> BoolSource

Returns true if class is abstract.

classHasSuperAttribute :: Class -> BoolSource

Returns true if class was annotated with the super attribute.

classInterfaces :: Class -> [String]Source

Returns interfaces this clas implements

classFields :: Class -> [Field]Source

Returns fields in the class

classMethods :: Class -> [Method]Source

Returns methods in class

classAttributes :: Class -> [Attribute]Source

Returns user-defined attributes on class.

loadClass :: FilePath -> IO ClassSource

Loads class at given path.

lookupMethod :: Class -> MethodKey -> Maybe MethodSource

Returns method with given key in class or Nothing if no method with that key is found.

Field declarations

data FieldId Source

Unique identifier of field

Constructors

FieldId 

Fields

fieldIdClass :: !String

Class name

fieldIdName :: !String

Field name

fieldIdType :: !Type

Field type

data Field Source

A class instance of static field

Instances

fieldName :: Field -> StringSource

Returns name of field.

fieldType :: Field -> TypeSource

Returns type of field.

fieldVisibility :: Field -> VisibilitySource

Returns visibility of field.

fieldIsStatic :: Field -> BoolSource

Returns true if field is static.

fieldIsFinal :: Field -> BoolSource

Returns true if field is final.

fieldIsVolatile :: Field -> BoolSource

Returns true if field is volatile.

fieldIsTransient :: Field -> BoolSource

Returns true if field is transient.

fieldConstantValue :: Field -> Maybe ConstantPoolValueSource

Returns initial value of field or Nothing if not assigned.

Only static fields may have a constant value.

fieldIsSynthetic :: Field -> BoolSource

Returns true if field is synthetic.

fieldIsDeprecated :: Field -> BoolSource

Returns true if field is deprecated.

fieldIsEnum :: Field -> BoolSource

Returns true if field is transient.

Method declarations

data MethodKey Source

A unique identifier for looking up a method in a class.

makeMethodKeySource

Arguments

:: String

Method name

-> String

Method descriptor

-> MethodKey 

Returns method key with the given name and descriptor.

methodName :: Method -> StringSource

Returns name of method

methodParameterTypes :: Method -> [Type]Source

Return parameter types for method.

localIndexOfParameter :: Method -> Int -> LocalVariableIndexSource

Returns the local variable index that the parameter is stored in when the method is invoked.

methodReturnType :: Method -> Maybe TypeSource

Return parameter types for method.

methodMaxLocals :: Method -> LocalVariableIndexSource

Returns maxinum number of local variables in method.

methodIsAbstract :: Method -> BoolSource

Returns true if method is abstract.

data MethodBody Source

Constructors

Code Word16 Word16 CFG [ExceptionTableEntry] LineNumberTable LocalVariableTable [Attribute] 
AbstractMethod 
NativeMethod 

methodExceptionTable :: Method -> [ExceptionTableEntry]Source

Exception table entries for method.

Instruction declarations

type LocalVariableIndex = Word16Source

A local variable index.

type PC = Word16Source

A program counter value.

data Instruction Source

A JVM Instruction

Constructors

Aaload 
Aastore 
Aconst_null 
Aload LocalVariableIndex 
Areturn 
Arraylength 
Astore LocalVariableIndex 
Athrow 
Baload 
Bastore 
Caload 
Castore 
Checkcast Type 
D2f 
D2i 
D2l 
Dadd 
Daload 
Dastore 
Dcmpg 
Dcmpl 
Ddiv 
Dload LocalVariableIndex 
Dmul 
Dneg 
Drem 
Dreturn 
Dstore LocalVariableIndex 
Dsub 
Dup 
Dup_x1 
Dup_x2 
Dup2 
Dup2_x1 
Dup2_x2 
F2d 
F2i 
F2l 
Fadd 
Faload 
Fastore 
Fcmpg 
Fcmpl 
Fdiv 
Fload LocalVariableIndex 
Fmul 
Fneg 
Frem 
Freturn 
Fstore LocalVariableIndex 
Fsub 
Getfield FieldId

getfield instruction

Getstatic FieldId 
Goto PC 
I2b 
I2c 
I2d 
I2f 
I2l 
I2s 
Iadd 
Iaload 
Iand 
Iastore 
Idiv 
If_acmpeq PC 
If_acmpne PC 
If_icmpeq PC 
If_icmpne PC 
If_icmplt PC 
If_icmpge PC 
If_icmpgt PC 
If_icmple PC 
Ifeq PC 
Ifne PC 
Iflt PC 
Ifge PC 
Ifgt PC 
Ifle PC 
Ifnonnull PC 
Ifnull PC 
Iinc LocalVariableIndex Int16 
Iload LocalVariableIndex 
Imul 
Ineg 
Instanceof Type 
Invokeinterface String MethodKey 
Invokespecial Type MethodKey 
Invokestatic String MethodKey 
Invokevirtual Type MethodKey 
Ior 
Irem 
Ireturn 
Ishl 
Ishr 
Istore LocalVariableIndex 
Isub 
Iushr 
Ixor 
Jsr PC 
L2d 
L2f 
L2i 
Ladd 
Laload 
Land 
Lastore 
Lcmp 
Ldc ConstantPoolValue 
Ldiv 
Lload LocalVariableIndex 
Lmul 
Lneg 
Lookupswitch PC [(Int32, PC)] 
Lor 
Lrem 
Lreturn 
Lshl 
Lshr 
Lstore LocalVariableIndex 
Lsub 
Lushr 
Lxor 
Monitorenter 
Monitorexit 
Multianewarray Type Word8 
New String 
Newarray Type 
Nop 
Pop 
Pop2 
Putfield FieldId 
Putstatic FieldId 
Ret LocalVariableIndex 
Return 
Saload 
Sastore 
Swap 
Tableswitch PC Int32 Int32 [PC] 

Exception table declarations

data ExceptionTableEntry Source

An entry in the exception table for a method

catchType :: ExceptionTableEntry -> Maybe TypeSource

The type of exception that should be caught or Nothing if all types of exceptions should be caught.

startPc :: ExceptionTableEntry -> PCSource

The starting program counter value where the exception handler applies

endPc :: ExceptionTableEntry -> PCSource

The ending program counter value where the exception handler applies.

handlerPc :: ExceptionTableEntry -> PCSource

The program counter value to jump to when an exception is caught.

Misc utility functions/values

Debugging information

hasDebugInfo :: Method -> BoolSource

Returns true if method has debug informaiton available.

classSourceFile :: Class -> Maybe StringSource

Returns name of source file where class was defined.

sourceLineNumberOrPrev :: Method -> PC -> Maybe Word16Source

Returns source line number of an instruction in a method at a given PC, or the line number of the nearest predecessor instruction, or Nothing if neither is available.

lookupLineStartPC :: Method -> Word16 -> Maybe PCSource

Returns the starting PC for the source at the given line number.

lookupLineMethodStartPC :: Class -> Word16 -> Maybe (Method, PC)Source

Returns the enclosing method and starting PC for the source at the given line number.

lookupLocalVariableByIdx :: Method -> PC -> LocalVariableIndex -> Maybe LocalVariableTableEntrySource

Returns local variable entry at given PC and local variable index or Nothing if no mapping is found.

lookupLocalVariableByName :: Method -> PC -> String -> Maybe LocalVariableTableEntrySource

Returns local variable entry at given PC and local variable string or Nothing if no mapping is found.

slashesToDots :: String -> StringSource

Replace / characters with . characters

cfgToDotSource

Arguments

:: ExceptionTable 
-> CFG 
-> String

method name

-> String 

Render the CFG of a method into Graphviz .dot format