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

Safe HaskellNone

JVM.Builder.Monad

Description

This module defines Generate[IO] monad, which helps generating JVM code and creating Java class constants pool.

Code generation could be done using one of two monads: Generate and GenerateIO. Generate monad is pure (simply State monad), while GenerateIO is IO-related. In GenerateIO additional actions are available, such as setting up ClassPath and loading classes (from .class files or JAR archives).

Synopsis

Documentation

data GState Source

Generator state

Constructors

GState 

Fields

generated :: [Instruction]

Already generated code (in current method)

currentPool :: Pool Direct

Already generated constants pool

nextPoolIndex :: Word16

Next index to be used in constants pool

doneMethods :: [Method Direct]

Already generated class methods

currentMethod :: Maybe (Method Direct)

Current method

stackSize :: Word16

Maximum stack size for current method

locals :: Word16

Maximum number of local variables for current method

classPath :: [Tree CPEntry]
 

emptyGState :: GStateSource

Empty generator state

class (Monad (g e), MonadState GState (g e)) => Generator e g whereSource

Methods

throwG :: (Exception x, Throws x e) => x -> g e aSource

data Generate e a Source

Generate monad

data GenerateIO e a Source

IO version of Generate monad

addToPool :: Generator e g => Constant Direct -> g e Word16Source

Add a constant into pool

i0 :: Generator e g => Instruction -> g e ()Source

Generate one (zero-arguments) instruction

i1 :: Generator e g => (Word16 -> Instruction) -> Constant Direct -> g e ()Source

Generate one one-argument instruction

i8 :: Generator e g => (Word8 -> Instruction) -> Constant Direct -> g e ()Source

Generate one one-argument instruction

newMethodSource

Arguments

:: (Generator e g, Throws UnexpectedEndMethod e) 
=> [AccessFlag]

Access flags for method (public, static etc)

-> ByteString

Method name

-> [ArgumentSignature]

Signatures of method arguments

-> ReturnSignature

Method return signature

-> g e ()

Generator for method code

-> g e (NameType (Method Direct)) 

Generate new method

setStackSize :: Generator e g => Word16 -> g e ()Source

Set maximum stack size for current method

setMaxLocals :: Generator e g => Word16 -> g e ()Source

Set maximum number of local variables for current method

withClassPath :: ClassPath () -> GenerateIO e ()Source

Update ClassPath

getClassField :: (Throws ENotFound e, Throws ENotLoaded e) => String -> ByteString -> GenerateIO e (NameType (Field Direct))Source

Get class field signature from current ClassPath

getClassMethod :: (Throws ENotFound e, Throws ENotLoaded e) => String -> ByteString -> GenerateIO e (NameType (Method Direct))Source

Get class method signature from current ClassPath