jvm-binary-0.1.0: A library for reading Java class-files

Copyright(c) Christian Gram Kalhauge 2018
LicenseMIT
Maintainerkalhuage@cs.ucla.edu
Safe HaskellNone
LanguageHaskell2010

Language.JVM.Attribute.Code

Description

 

Synopsis

Documentation

data Code r Source #

Code contains the actual byte-code. The i type parameter is added to allow indicate the two stages of the code file, before and after access to the ConstantPool. i should be either Ref or Deref.

Instances

Staged Code Source # 

Methods

stage :: LabelM m => (forall (s' :: * -> *). Staged s' => s' r -> m (s' r')) -> Code r -> m (Code r') Source #

evolve :: EvolveM m => Code Low -> m (Code High) Source #

devolve :: DevolveM m => Code High -> m (Code Low) Source #

Eq (Code High) Source # 

Methods

(==) :: Code High -> Code High -> Bool #

(/=) :: Code High -> Code High -> Bool #

Eq (Code Low) Source # 

Methods

(==) :: Code Low -> Code Low -> Bool #

(/=) :: Code Low -> Code Low -> Bool #

Ord (Code Low) Source # 

Methods

compare :: Code Low -> Code Low -> Ordering #

(<) :: Code Low -> Code Low -> Bool #

(<=) :: Code Low -> Code Low -> Bool #

(>) :: Code Low -> Code Low -> Bool #

(>=) :: Code Low -> Code Low -> Bool #

max :: Code Low -> Code Low -> Code Low #

min :: Code Low -> Code Low -> Code Low #

Show (Code High) Source # 
Show (Code Low) Source # 

Methods

showsPrec :: Int -> Code Low -> ShowS #

show :: Code Low -> String #

showList :: [Code Low] -> ShowS #

Generic (Code High) Source # 

Associated Types

type Rep (Code High) :: * -> * #

Methods

from :: Code High -> Rep (Code High) x #

to :: Rep (Code High) x -> Code High #

Generic (Code Low) Source # 

Associated Types

type Rep (Code Low) :: * -> * #

Methods

from :: Code Low -> Rep (Code Low) x #

to :: Rep (Code Low) x -> Code Low #

Binary (Code Low) Source # 

Methods

put :: Code Low -> Put #

get :: Get (Code Low) #

putList :: [Code Low] -> Put #

NFData (Code High) Source # 

Methods

rnf :: Code High -> () #

NFData (Code Low) Source # 

Methods

rnf :: Code Low -> () #

IsAttribute (Code Low) Source #

Code is an Attribute.

type Rep (Code High) Source # 
type Rep (Code Low) Source # 

data CodeAttributes r Source #

Instances

Eq (CodeAttributes High) Source # 
Eq (CodeAttributes Low) Source # 
Ord (CodeAttributes Low) Source # 
Show (CodeAttributes High) Source # 
Show (CodeAttributes Low) Source # 
Generic (CodeAttributes High) Source # 

Associated Types

type Rep (CodeAttributes High) :: * -> * #

Generic (CodeAttributes Low) Source # 

Associated Types

type Rep (CodeAttributes Low) :: * -> * #

NFData (CodeAttributes High) Source # 

Methods

rnf :: CodeAttributes High -> () #

NFData (CodeAttributes Low) Source # 

Methods

rnf :: CodeAttributes Low -> () #

type Rep (CodeAttributes High) Source # 
type Rep (CodeAttributes High) = D1 * (MetaData "CodeAttributes" "Language.JVM.Attribute.Code" "jvm-binary-0.1.0-JJ8Rr7ERir79pQaBJvdiXV" False) (C1 * (MetaCons "CodeAttributes" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "caStackMapTable") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [StackMapTable High])) ((:*:) * (S1 * (MetaSel (Just Symbol "caLineNumberTable") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [LineNumberTable High])) (S1 * (MetaSel (Just Symbol "caOthers") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [Attribute High])))))
type Rep (CodeAttributes Low) Source # 
type Rep (CodeAttributes Low) = D1 * (MetaData "CodeAttributes" "Language.JVM.Attribute.Code" "jvm-binary-0.1.0-JJ8Rr7ERir79pQaBJvdiXV" False) (C1 * (MetaCons "CodeAttributes" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "caStackMapTable") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [StackMapTable Low])) ((:*:) * (S1 * (MetaSel (Just Symbol "caLineNumberTable") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [LineNumberTable Low])) (S1 * (MetaSel (Just Symbol "caOthers") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [Attribute Low])))))

data ExceptionTable r Source #

Constructors

ExceptionTable 

Fields

Instances

ByteCodeStaged ExceptionTable Source # 
Eq (ExceptionTable High) Source # 
Eq (ExceptionTable Low) Source # 
Ord (ExceptionTable Low) Source # 
Show (ExceptionTable High) Source # 
Show (ExceptionTable Low) Source # 
Generic (ExceptionTable High) Source # 

Associated Types

type Rep (ExceptionTable High) :: * -> * #

Generic (ExceptionTable Low) Source # 

Associated Types

type Rep (ExceptionTable Low) :: * -> * #

Binary (ExceptionTable Low) Source # 
NFData (ExceptionTable High) Source # 

Methods

rnf :: ExceptionTable High -> () #

NFData (ExceptionTable Low) Source # 

Methods

rnf :: ExceptionTable Low -> () #

type Rep (ExceptionTable High) Source # 
type Rep (ExceptionTable Low) Source # 

codeStackMapTable :: Code High -> Maybe (StackMapTable High) Source #

Returns the StackMapTable attribute if any

codeByteCodeOprs :: Code High -> Vector (ByteCodeOpr High) Source #

Extracts a list of bytecode operation

codeByteCodeInsts :: Code Low -> Vector (ByteCodeInst Low) Source #

Extracts a list of bytecode instructions