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

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

Language.JVM.Stage

Description

This module contains the stages, there are two stages; Low and High. Low represents closest to the metal and High represents closer to the conceptual representation.

Synopsis

Documentation

data Low Source #

Any data structure that is in the low stage should be serializable using the binary library.

Instances
Eq (InvokeDynamic Low) Source # 
Instance details

Defined in Language.JVM.Constant

Eq (MethodHandleInterface Low) Source # 
Instance details

Defined in Language.JVM.Constant

Eq (MethodHandleMethod Low) Source # 
Instance details

Defined in Language.JVM.Constant

Eq (MethodHandleField Low) Source # 
Instance details

Defined in Language.JVM.Constant

Eq (MethodHandle Low) Source # 
Instance details

Defined in Language.JVM.Constant

Eq (AbsVariableMethodId Low) Source # 
Instance details

Defined in Language.JVM.Constant

Eq (AbsInterfaceMethodId Low) Source # 
Instance details

Defined in Language.JVM.Constant

Eq (Constant Low) Source # 
Instance details

Defined in Language.JVM.Constant

Eq (ConstantPool Low) Source # 
Instance details

Defined in Language.JVM.ConstantPool

Eq (ByteCodeOpr Low) Source # 
Instance details

Defined in Language.JVM.ByteCode

Eq (SwitchTable Low) Source # 
Instance details

Defined in Language.JVM.ByteCode

Eq (CConstant Low) Source # 
Instance details

Defined in Language.JVM.ByteCode

Eq (Invocation Low) Source # 
Instance details

Defined in Language.JVM.ByteCode

Eq (ByteCodeInst Low) Source # 
Instance details

Defined in Language.JVM.ByteCode

Eq (ByteCode Low) Source # 
Instance details

Defined in Language.JVM.ByteCode

Eq (Attribute Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Base

Eq (VerificationTypeInfo Low) Source # 
Instance details

Defined in Language.JVM.Attribute.StackMapTable

Eq (StackMapFrameType Low) Source # 
Instance details

Defined in Language.JVM.Attribute.StackMapTable

Eq (StackMapFrame Low) Source # 
Instance details

Defined in Language.JVM.Attribute.StackMapTable

Eq (StackMapTable Low) Source # 
Instance details

Defined in Language.JVM.Attribute.StackMapTable

Eq (Signature Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Signature

Eq (Exceptions Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Exceptions

Eq (EnclosingMethod Low) Source # 
Instance details

Defined in Language.JVM.Attribute.EnclosingMethod

Eq (ConstantValue Low) Source # 
Instance details

Defined in Language.JVM.Attribute.ConstantValue

Eq (CodeAttributes Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Code

Eq (ExceptionTable Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Code

Eq (Code Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Code

Methods

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

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

Eq (BootstrapMethod Low) Source # 
Instance details

Defined in Language.JVM.Attribute.BootstrapMethods

Eq (BootstrapMethods Low) Source # 
Instance details

Defined in Language.JVM.Attribute.BootstrapMethods

Eq (MethodAttributes Low) Source # 
Instance details

Defined in Language.JVM.Method

Eq (Method Low) Source # 
Instance details

Defined in Language.JVM.Method

Methods

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

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

Eq (FieldAttributes Low) Source # 
Instance details

Defined in Language.JVM.Field

Eq (Field Low) Source # 
Instance details

Defined in Language.JVM.Field

Methods

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

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

Eq (InnerClass Low) Source # 
Instance details

Defined in Language.JVM.Attribute.InnerClasses

Eq (InnerClasses Low) Source # 
Instance details

Defined in Language.JVM.Attribute.InnerClasses

Eq (ClassAttributes Low) Source # 
Instance details

Defined in Language.JVM.ClassFile

Eq (ClassFile Low) Source # 
Instance details

Defined in Language.JVM.ClassFile

Ord (InvokeDynamic Low) Source # 
Instance details

Defined in Language.JVM.Constant

Ord (MethodHandleInterface Low) Source # 
Instance details

Defined in Language.JVM.Constant

Ord (MethodHandleMethod Low) Source # 
Instance details

Defined in Language.JVM.Constant

Ord (MethodHandleField Low) Source # 
Instance details

Defined in Language.JVM.Constant

Ord (MethodHandle Low) Source # 
Instance details

Defined in Language.JVM.Constant

Ord (AbsVariableMethodId Low) Source # 
Instance details

Defined in Language.JVM.Constant

Ord (AbsInterfaceMethodId Low) Source # 
Instance details

Defined in Language.JVM.Constant

Ord (Constant Low) Source # 
Instance details

Defined in Language.JVM.Constant

Ord (ConstantPool Low) Source # 
Instance details

Defined in Language.JVM.ConstantPool

Ord (ByteCodeOpr Low) Source # 
Instance details

Defined in Language.JVM.ByteCode

Ord (SwitchTable Low) Source # 
Instance details

Defined in Language.JVM.ByteCode

Ord (CConstant Low) Source # 
Instance details

Defined in Language.JVM.ByteCode

Ord (Invocation Low) Source # 
Instance details

Defined in Language.JVM.ByteCode

Ord (ByteCodeInst Low) Source # 
Instance details

Defined in Language.JVM.ByteCode

Ord (ByteCode Low) Source # 
Instance details

Defined in Language.JVM.ByteCode

Ord (Attribute Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Base

Ord (VerificationTypeInfo Low) Source # 
Instance details

Defined in Language.JVM.Attribute.StackMapTable

Ord (StackMapFrameType Low) Source # 
Instance details

Defined in Language.JVM.Attribute.StackMapTable

Ord (StackMapFrame Low) Source # 
Instance details

Defined in Language.JVM.Attribute.StackMapTable

Ord (StackMapTable Low) Source # 
Instance details

Defined in Language.JVM.Attribute.StackMapTable

Ord (Signature Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Signature

Ord (Exceptions Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Exceptions

Ord (EnclosingMethod Low) Source # 
Instance details

Defined in Language.JVM.Attribute.EnclosingMethod

Ord (ConstantValue Low) Source # 
Instance details

Defined in Language.JVM.Attribute.ConstantValue

Ord (CodeAttributes Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Code

Ord (ExceptionTable Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Code

Ord (Code Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Code

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 #

Ord (BootstrapMethod Low) Source # 
Instance details

Defined in Language.JVM.Attribute.BootstrapMethods

Ord (BootstrapMethods Low) Source # 
Instance details

Defined in Language.JVM.Attribute.BootstrapMethods

Ord (MethodAttributes Low) Source # 
Instance details

Defined in Language.JVM.Method

Ord (Method Low) Source # 
Instance details

Defined in Language.JVM.Method

Ord (FieldAttributes Low) Source # 
Instance details

Defined in Language.JVM.Field

Ord (Field Low) Source # 
Instance details

Defined in Language.JVM.Field

Ord (InnerClass Low) Source # 
Instance details

Defined in Language.JVM.Attribute.InnerClasses

Ord (InnerClasses Low) Source # 
Instance details

Defined in Language.JVM.Attribute.InnerClasses

Ord (ClassAttributes Low) Source # 
Instance details

Defined in Language.JVM.ClassFile

Ord (ClassFile Low) Source # 
Instance details

Defined in Language.JVM.ClassFile

Show (InvokeDynamic Low) Source # 
Instance details

Defined in Language.JVM.Constant

Show (MethodHandleInterface Low) Source # 
Instance details

Defined in Language.JVM.Constant

Show (MethodHandleMethod Low) Source # 
Instance details

Defined in Language.JVM.Constant

Show (MethodHandleField Low) Source # 
Instance details

Defined in Language.JVM.Constant

Show (MethodHandle Low) Source # 
Instance details

Defined in Language.JVM.Constant

Show (AbsVariableMethodId Low) Source # 
Instance details

Defined in Language.JVM.Constant

Show (AbsInterfaceMethodId Low) Source # 
Instance details

Defined in Language.JVM.Constant

Show (Constant Low) Source # 
Instance details

Defined in Language.JVM.Constant

Show (ConstantPool Low) Source # 
Instance details

Defined in Language.JVM.ConstantPool

Show (ByteCodeOpr Low) Source # 
Instance details

Defined in Language.JVM.ByteCode

Show (SwitchTable Low) Source # 
Instance details

Defined in Language.JVM.ByteCode

Show (CConstant Low) Source # 
Instance details

Defined in Language.JVM.ByteCode

Show (Invocation Low) Source # 
Instance details

Defined in Language.JVM.ByteCode

Show (ByteCodeInst Low) Source # 
Instance details

Defined in Language.JVM.ByteCode

Show (ByteCode Low) Source # 
Instance details

Defined in Language.JVM.ByteCode

Show (Attribute Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Base

Show (VerificationTypeInfo Low) Source # 
Instance details

Defined in Language.JVM.Attribute.StackMapTable

Show (StackMapFrameType Low) Source # 
Instance details

Defined in Language.JVM.Attribute.StackMapTable

Show (StackMapFrame Low) Source # 
Instance details

Defined in Language.JVM.Attribute.StackMapTable

Show (StackMapTable Low) Source # 
Instance details

Defined in Language.JVM.Attribute.StackMapTable

Show (Signature Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Signature

Show (Exceptions Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Exceptions

Show (EnclosingMethod Low) Source # 
Instance details

Defined in Language.JVM.Attribute.EnclosingMethod

Show (ConstantValue Low) Source # 
Instance details

Defined in Language.JVM.Attribute.ConstantValue

Show (CodeAttributes Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Code

Show (ExceptionTable Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Code

Show (Code Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Code

Methods

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

show :: Code Low -> String #

showList :: [Code Low] -> ShowS #

Show (BootstrapMethod Low) Source # 
Instance details

Defined in Language.JVM.Attribute.BootstrapMethods

Show (BootstrapMethods Low) Source # 
Instance details

Defined in Language.JVM.Attribute.BootstrapMethods

Show (MethodAttributes Low) Source # 
Instance details

Defined in Language.JVM.Method

Show (Method Low) Source # 
Instance details

Defined in Language.JVM.Method

Show (FieldAttributes Low) Source # 
Instance details

Defined in Language.JVM.Field

Show (Field Low) Source # 
Instance details

Defined in Language.JVM.Field

Show (InnerClass Low) Source # 
Instance details

Defined in Language.JVM.Attribute.InnerClasses

Show (InnerClasses Low) Source # 
Instance details

Defined in Language.JVM.Attribute.InnerClasses

Show (ClassAttributes Low) Source # 
Instance details

Defined in Language.JVM.ClassFile

Show (ClassFile Low) Source # 
Instance details

Defined in Language.JVM.ClassFile

Generic (InvokeDynamic Low) Source # 
Instance details

Defined in Language.JVM.Constant

Associated Types

type Rep (InvokeDynamic Low) :: Type -> Type #

Generic (MethodHandleInterface Low) Source # 
Instance details

Defined in Language.JVM.Constant

Associated Types

type Rep (MethodHandleInterface Low) :: Type -> Type #

Generic (MethodHandleMethod Low) Source # 
Instance details

Defined in Language.JVM.Constant

Associated Types

type Rep (MethodHandleMethod Low) :: Type -> Type #

Generic (MethodHandleField Low) Source # 
Instance details

Defined in Language.JVM.Constant

Associated Types

type Rep (MethodHandleField Low) :: Type -> Type #

Generic (MethodHandle Low) Source # 
Instance details

Defined in Language.JVM.Constant

Associated Types

type Rep (MethodHandle Low) :: Type -> Type #

Generic (AbsVariableMethodId Low) Source # 
Instance details

Defined in Language.JVM.Constant

Associated Types

type Rep (AbsVariableMethodId Low) :: Type -> Type #

Generic (AbsInterfaceMethodId Low) Source # 
Instance details

Defined in Language.JVM.Constant

Associated Types

type Rep (AbsInterfaceMethodId Low) :: Type -> Type #

Generic (Constant Low) Source # 
Instance details

Defined in Language.JVM.Constant

Associated Types

type Rep (Constant Low) :: Type -> Type #

Methods

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

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

Generic (ConstantPool Low) Source # 
Instance details

Defined in Language.JVM.ConstantPool

Associated Types

type Rep (ConstantPool Low) :: Type -> Type #

Generic (ByteCodeOpr Low) Source # 
Instance details

Defined in Language.JVM.ByteCode

Associated Types

type Rep (ByteCodeOpr Low) :: Type -> Type #

Generic (SwitchTable Low) Source # 
Instance details

Defined in Language.JVM.ByteCode

Associated Types

type Rep (SwitchTable Low) :: Type -> Type #

Generic (CConstant Low) Source # 
Instance details

Defined in Language.JVM.ByteCode

Associated Types

type Rep (CConstant Low) :: Type -> Type #

Generic (Invocation Low) Source # 
Instance details

Defined in Language.JVM.ByteCode

Associated Types

type Rep (Invocation Low) :: Type -> Type #

Generic (ByteCodeInst Low) Source # 
Instance details

Defined in Language.JVM.ByteCode

Associated Types

type Rep (ByteCodeInst Low) :: Type -> Type #

Generic (ByteCode Low) Source # 
Instance details

Defined in Language.JVM.ByteCode

Associated Types

type Rep (ByteCode Low) :: Type -> Type #

Methods

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

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

Generic (Attribute Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Base

Associated Types

type Rep (Attribute Low) :: Type -> Type #

Generic (VerificationTypeInfo Low) Source # 
Instance details

Defined in Language.JVM.Attribute.StackMapTable

Associated Types

type Rep (VerificationTypeInfo Low) :: Type -> Type #

Generic (StackMapFrameType Low) Source # 
Instance details

Defined in Language.JVM.Attribute.StackMapTable

Associated Types

type Rep (StackMapFrameType Low) :: Type -> Type #

Generic (StackMapFrame Low) Source # 
Instance details

Defined in Language.JVM.Attribute.StackMapTable

Associated Types

type Rep (StackMapFrame Low) :: Type -> Type #

Generic (StackMapTable Low) Source # 
Instance details

Defined in Language.JVM.Attribute.StackMapTable

Associated Types

type Rep (StackMapTable Low) :: Type -> Type #

Generic (Signature Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Signature

Associated Types

type Rep (Signature Low) :: Type -> Type #

Generic (Exceptions Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Exceptions

Associated Types

type Rep (Exceptions Low) :: Type -> Type #

Generic (EnclosingMethod Low) Source # 
Instance details

Defined in Language.JVM.Attribute.EnclosingMethod

Associated Types

type Rep (EnclosingMethod Low) :: Type -> Type #

Generic (ConstantValue Low) Source # 
Instance details

Defined in Language.JVM.Attribute.ConstantValue

Associated Types

type Rep (ConstantValue Low) :: Type -> Type #

Generic (CodeAttributes Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Code

Associated Types

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

Generic (ExceptionTable Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Code

Associated Types

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

Generic (Code Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Code

Associated Types

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

Methods

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

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

Generic (BootstrapMethod Low) Source # 
Instance details

Defined in Language.JVM.Attribute.BootstrapMethods

Associated Types

type Rep (BootstrapMethod Low) :: Type -> Type #

Generic (BootstrapMethods Low) Source # 
Instance details

Defined in Language.JVM.Attribute.BootstrapMethods

Associated Types

type Rep (BootstrapMethods Low) :: Type -> Type #

Generic (MethodAttributes Low) Source # 
Instance details

Defined in Language.JVM.Method

Associated Types

type Rep (MethodAttributes Low) :: Type -> Type #

Generic (Method Low) Source # 
Instance details

Defined in Language.JVM.Method

Associated Types

type Rep (Method Low) :: Type -> Type #

Methods

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

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

Generic (FieldAttributes Low) Source # 
Instance details

Defined in Language.JVM.Field

Associated Types

type Rep (FieldAttributes Low) :: Type -> Type #

Generic (Field Low) Source # 
Instance details

Defined in Language.JVM.Field

Associated Types

type Rep (Field Low) :: Type -> Type #

Methods

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

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

Generic (InnerClass Low) Source # 
Instance details

Defined in Language.JVM.Attribute.InnerClasses

Associated Types

type Rep (InnerClass Low) :: Type -> Type #

Generic (InnerClasses Low) Source # 
Instance details

Defined in Language.JVM.Attribute.InnerClasses

Associated Types

type Rep (InnerClasses Low) :: Type -> Type #

Generic (ClassAttributes Low) Source # 
Instance details

Defined in Language.JVM.ClassFile

Associated Types

type Rep (ClassAttributes Low) :: Type -> Type #

Generic (ClassFile Low) Source # 
Instance details

Defined in Language.JVM.ClassFile

Associated Types

type Rep (ClassFile Low) :: Type -> Type #

Binary (InvokeDynamic Low) Source # 
Instance details

Defined in Language.JVM.Constant

Binary (MethodHandle Low) Source # 
Instance details

Defined in Language.JVM.Constant

Binary (AbsVariableMethodId Low) Source # 
Instance details

Defined in Language.JVM.Constant

Binary (AbsInterfaceMethodId Low) Source # 
Instance details

Defined in Language.JVM.Constant

Binary (Constant Low) Source # 
Instance details

Defined in Language.JVM.Constant

Binary (ConstantPool Low) Source # 
Instance details

Defined in Language.JVM.ConstantPool

Binary (ByteCodeOpr Low) Source # 
Instance details

Defined in Language.JVM.ByteCode

Binary (ByteCodeInst Low) Source # 
Instance details

Defined in Language.JVM.ByteCode

Binary (ByteCode Low) Source # 
Instance details

Defined in Language.JVM.ByteCode

Binary (Attribute Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Base

Binary (VerificationTypeInfo Low) Source # 
Instance details

Defined in Language.JVM.Attribute.StackMapTable

Binary (StackMapFrame Low) Source # 
Instance details

Defined in Language.JVM.Attribute.StackMapTable

Binary (StackMapTable Low) Source # 
Instance details

Defined in Language.JVM.Attribute.StackMapTable

Binary (Signature Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Signature

Binary (LineNumberTable Low) Source # 
Instance details

Defined in Language.JVM.Attribute.LineNumberTable

Binary (Exceptions Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Exceptions

Binary (EnclosingMethod Low) Source # 
Instance details

Defined in Language.JVM.Attribute.EnclosingMethod

Binary (ConstantValue Low) Source # 
Instance details

Defined in Language.JVM.Attribute.ConstantValue

Binary (ExceptionTable Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Code

Binary (Code Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Code

Methods

put :: Code Low -> Put #

get :: Get (Code Low) #

putList :: [Code Low] -> Put #

Binary (BootstrapMethod Low) Source # 
Instance details

Defined in Language.JVM.Attribute.BootstrapMethods

Binary (BootstrapMethods Low) Source # 
Instance details

Defined in Language.JVM.Attribute.BootstrapMethods

Binary (Method Low) Source # 
Instance details

Defined in Language.JVM.Method

Methods

put :: Method Low -> Put #

get :: Get (Method Low) #

putList :: [Method Low] -> Put #

Binary (Field Low) Source # 
Instance details

Defined in Language.JVM.Field

Methods

put :: Field Low -> Put #

get :: Get (Field Low) #

putList :: [Field Low] -> Put #

Binary (InnerClass Low) Source # 
Instance details

Defined in Language.JVM.Attribute.InnerClasses

Binary (InnerClasses Low) Source # 
Instance details

Defined in Language.JVM.Attribute.InnerClasses

Binary (ClassFile Low) Source # 
Instance details

Defined in Language.JVM.ClassFile

NFData (InvokeDynamic Low) Source # 
Instance details

Defined in Language.JVM.Constant

Methods

rnf :: InvokeDynamic Low -> () #

NFData (MethodHandleInterface Low) Source # 
Instance details

Defined in Language.JVM.Constant

Methods

rnf :: MethodHandleInterface Low -> () #

NFData (MethodHandleMethod Low) Source # 
Instance details

Defined in Language.JVM.Constant

Methods

rnf :: MethodHandleMethod Low -> () #

NFData (MethodHandleField Low) Source # 
Instance details

Defined in Language.JVM.Constant

Methods

rnf :: MethodHandleField Low -> () #

NFData (MethodHandle Low) Source # 
Instance details

Defined in Language.JVM.Constant

Methods

rnf :: MethodHandle Low -> () #

NFData (AbsVariableMethodId Low) Source # 
Instance details

Defined in Language.JVM.Constant

Methods

rnf :: AbsVariableMethodId Low -> () #

NFData (AbsInterfaceMethodId Low) Source # 
Instance details

Defined in Language.JVM.Constant

Methods

rnf :: AbsInterfaceMethodId Low -> () #

NFData (Constant Low) Source # 
Instance details

Defined in Language.JVM.Constant

Methods

rnf :: Constant Low -> () #

NFData (ConstantPool Low) Source # 
Instance details

Defined in Language.JVM.ConstantPool

Methods

rnf :: ConstantPool Low -> () #

NFData (ByteCodeOpr Low) Source # 
Instance details

Defined in Language.JVM.ByteCode

Methods

rnf :: ByteCodeOpr Low -> () #

NFData (SwitchTable Low) Source # 
Instance details

Defined in Language.JVM.ByteCode

Methods

rnf :: SwitchTable Low -> () #

NFData (CConstant Low) Source # 
Instance details

Defined in Language.JVM.ByteCode

Methods

rnf :: CConstant Low -> () #

NFData (Invocation Low) Source # 
Instance details

Defined in Language.JVM.ByteCode

Methods

rnf :: Invocation Low -> () #

NFData (ByteCodeInst Low) Source # 
Instance details

Defined in Language.JVM.ByteCode

Methods

rnf :: ByteCodeInst Low -> () #

NFData (ByteCode Low) Source # 
Instance details

Defined in Language.JVM.ByteCode

Methods

rnf :: ByteCode Low -> () #

NFData (Attribute Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Base

Methods

rnf :: Attribute Low -> () #

NFData (VerificationTypeInfo Low) Source # 
Instance details

Defined in Language.JVM.Attribute.StackMapTable

Methods

rnf :: VerificationTypeInfo Low -> () #

NFData (StackMapFrameType Low) Source # 
Instance details

Defined in Language.JVM.Attribute.StackMapTable

Methods

rnf :: StackMapFrameType Low -> () #

NFData (StackMapFrame Low) Source # 
Instance details

Defined in Language.JVM.Attribute.StackMapTable

Methods

rnf :: StackMapFrame Low -> () #

NFData (StackMapTable Low) Source # 
Instance details

Defined in Language.JVM.Attribute.StackMapTable

Methods

rnf :: StackMapTable Low -> () #

NFData (Signature Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Signature

Methods

rnf :: Signature Low -> () #

NFData (Exceptions Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Exceptions

Methods

rnf :: Exceptions Low -> () #

NFData (EnclosingMethod Low) Source # 
Instance details

Defined in Language.JVM.Attribute.EnclosingMethod

Methods

rnf :: EnclosingMethod Low -> () #

NFData (ConstantValue Low) Source # 
Instance details

Defined in Language.JVM.Attribute.ConstantValue

Methods

rnf :: ConstantValue Low -> () #

NFData (CodeAttributes Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Code

Methods

rnf :: CodeAttributes Low -> () #

NFData (ExceptionTable Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Code

Methods

rnf :: ExceptionTable Low -> () #

NFData (Code Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Code

Methods

rnf :: Code Low -> () #

NFData (BootstrapMethod Low) Source # 
Instance details

Defined in Language.JVM.Attribute.BootstrapMethods

Methods

rnf :: BootstrapMethod Low -> () #

NFData (BootstrapMethods Low) Source # 
Instance details

Defined in Language.JVM.Attribute.BootstrapMethods

Methods

rnf :: BootstrapMethods Low -> () #

NFData (MethodAttributes Low) Source # 
Instance details

Defined in Language.JVM.Method

Methods

rnf :: MethodAttributes Low -> () #

NFData (Method Low) Source # 
Instance details

Defined in Language.JVM.Method

Methods

rnf :: Method Low -> () #

NFData (FieldAttributes Low) Source # 
Instance details

Defined in Language.JVM.Field

Methods

rnf :: FieldAttributes Low -> () #

NFData (Field Low) Source # 
Instance details

Defined in Language.JVM.Field

Methods

rnf :: Field Low -> () #

NFData (InnerClass Low) Source # 
Instance details

Defined in Language.JVM.Attribute.InnerClasses

Methods

rnf :: InnerClass Low -> () #

NFData (InnerClasses Low) Source # 
Instance details

Defined in Language.JVM.Attribute.InnerClasses

Methods

rnf :: InnerClasses Low -> () #

NFData (ClassAttributes Low) Source # 
Instance details

Defined in Language.JVM.ClassFile

Methods

rnf :: ClassAttributes Low -> () #

NFData (ClassFile Low) Source # 
Instance details

Defined in Language.JVM.ClassFile

Methods

rnf :: ClassFile Low -> () #

IsAttribute (StackMapTable Low) Source #

StackMapTable is an Attribute.

Instance details

Defined in Language.JVM.Attribute.StackMapTable

IsAttribute (Signature Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Signature

IsAttribute (LineNumberTable Low) Source #

Signature is an Attribute.

Instance details

Defined in Language.JVM.Attribute.LineNumberTable

IsAttribute (Exceptions Low) Source #

Exceptions is an Attribute.

Instance details

Defined in Language.JVM.Attribute.Exceptions

IsAttribute (EnclosingMethod Low) Source #

EnclosingMethod is an Attribute.

Instance details

Defined in Language.JVM.Attribute.EnclosingMethod

IsAttribute (ConstantValue Low) Source #

ConstantValue is an Attribute.

Instance details

Defined in Language.JVM.Attribute.ConstantValue

IsAttribute (Code Low) Source #

Code is an Attribute.

Instance details

Defined in Language.JVM.Attribute.Code

IsAttribute (BootstrapMethods Low) Source #

BootstrapMethods is an Attribute.

Instance details

Defined in Language.JVM.Attribute.BootstrapMethods

IsAttribute (InnerClasses Low) Source #

InnerClasses is an Attribute.

Instance details

Defined in Language.JVM.Attribute.InnerClasses

Eq (InClass FieldId Low) Source # 
Instance details

Defined in Language.JVM.Constant

Eq (InClass MethodId Low) Source # 
Instance details

Defined in Language.JVM.Constant

Ord (InClass FieldId Low) Source # 
Instance details

Defined in Language.JVM.Constant

Ord (InClass MethodId Low) Source # 
Instance details

Defined in Language.JVM.Constant

Show (InClass FieldId Low) Source # 
Instance details

Defined in Language.JVM.Constant

Show (InClass MethodId Low) Source # 
Instance details

Defined in Language.JVM.Constant

Generic (InClass FieldId Low) Source # 
Instance details

Defined in Language.JVM.Constant

Associated Types

type Rep (InClass FieldId Low) :: Type -> Type #

Generic (InClass MethodId Low) Source # 
Instance details

Defined in Language.JVM.Constant

Associated Types

type Rep (InClass MethodId Low) :: Type -> Type #

Binary (InClass FieldId Low) Source # 
Instance details

Defined in Language.JVM.Constant

Binary (InClass MethodId Low) Source # 
Instance details

Defined in Language.JVM.Constant

NFData (InClass FieldId Low) Source # 
Instance details

Defined in Language.JVM.Constant

Methods

rnf :: InClass FieldId Low -> () #

NFData (InClass MethodId Low) Source # 
Instance details

Defined in Language.JVM.Constant

Methods

rnf :: InClass MethodId Low -> () #

type Choice a b Low Source # 
Instance details

Defined in Language.JVM.Stage

type Choice a b Low = a
type Rep (InvokeDynamic Low) Source # 
Instance details

Defined in Language.JVM.Constant

type Rep (InvokeDynamic Low) = D1 (MetaData "InvokeDynamic" "Language.JVM.Constant" "jvm-binary-0.5.0-8tjUXfOvOFm5evlZ3bpMMl" False) (C1 (MetaCons "InvokeDynamic" PrefixI True) (S1 (MetaSel (Just "invokeDynamicAttrIndex") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Word16) :*: S1 (MetaSel (Just "invokeDynamicMethod") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Ref MethodId Low))))
type Rep (MethodHandleInterface Low) Source # 
Instance details

Defined in Language.JVM.Constant

type Rep (MethodHandleInterface Low) = D1 (MetaData "MethodHandleInterface" "Language.JVM.Constant" "jvm-binary-0.5.0-8tjUXfOvOFm5evlZ3bpMMl" False) (C1 (MetaCons "MethodHandleInterface" PrefixI True) (S1 (MetaSel (Just "methodHandleInterfaceRef") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (DeepRef AbsInterfaceMethodId Low))))
type Rep (MethodHandleMethod Low) Source # 
Instance details

Defined in Language.JVM.Constant

type Rep (MethodHandleField Low) Source # 
Instance details

Defined in Language.JVM.Constant

type Rep (MethodHandleField Low) = D1 (MetaData "MethodHandleField" "Language.JVM.Constant" "jvm-binary-0.5.0-8tjUXfOvOFm5evlZ3bpMMl" False) (C1 (MetaCons "MethodHandleField" PrefixI True) (S1 (MetaSel (Just "methodHandleFieldKind") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 MethodHandleFieldKind) :*: S1 (MetaSel (Just "methodHandleFieldRef") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (DeepRef AbsFieldId Low))))
type Rep (MethodHandle Low) Source # 
Instance details

Defined in Language.JVM.Constant

type Rep (AbsVariableMethodId Low) Source # 
Instance details

Defined in Language.JVM.Constant

type Rep (AbsVariableMethodId Low) = D1 (MetaData "AbsVariableMethodId" "Language.JVM.Constant" "jvm-binary-0.5.0-8tjUXfOvOFm5evlZ3bpMMl" False) (C1 (MetaCons "AbsVariableMethodId" PrefixI True) (S1 (MetaSel (Just "variableIsInterface") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Bool) :*: S1 (MetaSel (Just "variableMethodId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (InClass MethodId Low))))
type Rep (AbsInterfaceMethodId Low) Source # 
Instance details

Defined in Language.JVM.Constant

type Rep (AbsInterfaceMethodId Low) = D1 (MetaData "AbsInterfaceMethodId" "Language.JVM.Constant" "jvm-binary-0.5.0-8tjUXfOvOFm5evlZ3bpMMl" True) (C1 (MetaCons "AbsInterfaceMethodId" PrefixI True) (S1 (MetaSel (Just "interfaceMethodId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (InClass MethodId Low))))
type Rep (Constant Low) Source # 
Instance details

Defined in Language.JVM.Constant

type Rep (Constant Low) = D1 (MetaData "Constant" "Language.JVM.Constant" "jvm-binary-0.5.0-8tjUXfOvOFm5evlZ3bpMMl" False) (((C1 (MetaCons "CString" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 SizedByteString16)) :+: (C1 (MetaCons "CInteger" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Int32)) :+: C1 (MetaCons "CFloat" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Float)))) :+: ((C1 (MetaCons "CLong" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Int64)) :+: C1 (MetaCons "CDouble" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Double))) :+: (C1 (MetaCons "CClassRef" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Ref Text Low))) :+: C1 (MetaCons "CStringRef" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Ref ByteString Low)))))) :+: ((C1 (MetaCons "CFieldRef" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (InClass FieldId Low))) :+: (C1 (MetaCons "CMethodRef" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (InClass MethodId Low))) :+: C1 (MetaCons "CInterfaceMethodRef" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (InClass MethodId Low))))) :+: ((C1 (MetaCons "CNameAndType" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Ref Text Low)) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Ref Text Low))) :+: C1 (MetaCons "CMethodHandle" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (MethodHandle Low)))) :+: (C1 (MetaCons "CMethodType" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Ref MethodDescriptor Low))) :+: C1 (MetaCons "CInvokeDynamic" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (InvokeDynamic Low)))))))
type Rep (ConstantPool Low) Source # 
Instance details

Defined in Language.JVM.ConstantPool

type Rep (ConstantPool Low) = D1 (MetaData "ConstantPool" "Language.JVM.ConstantPool" "jvm-binary-0.5.0-8tjUXfOvOFm5evlZ3bpMMl" True) (C1 (MetaCons "ConstantPool" PrefixI True) (S1 (MetaSel (Just "unConstantPool") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (IntMap (Constant Low)))))
type Rep (ByteCodeOpr Low) Source # 
Instance details

Defined in Language.JVM.ByteCode

type Rep (SwitchTable Low) Source # 
Instance details

Defined in Language.JVM.ByteCode

type Rep (CConstant Low) Source # 
Instance details

Defined in Language.JVM.ByteCode

type Rep (CConstant Low) = D1 (MetaData "CConstant" "Language.JVM.ByteCode" "jvm-binary-0.5.0-8tjUXfOvOFm5evlZ3bpMMl" False) ((((C1 (MetaCons "CNull" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "CIntM1" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "CInt0" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "CInt1" PrefixI False) (U1 :: Type -> Type))) :+: ((C1 (MetaCons "CInt2" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "CInt3" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "CInt4" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "CInt5" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "CLong0" PrefixI False) (U1 :: Type -> Type))))) :+: (((C1 (MetaCons "CLong1" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "CFloat0" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "CFloat1" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "CFloat2" PrefixI False) (U1 :: Type -> Type))) :+: ((C1 (MetaCons "CDouble0" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "CDouble1" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "CByte" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Int8)) :+: (C1 (MetaCons "CShort" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Int16)) :+: C1 (MetaCons "CRef" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 (Maybe WordSize)) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 (Ref JValue Low))))))))
type Rep (Invocation Low) Source # 
Instance details

Defined in Language.JVM.ByteCode

type Rep (ByteCodeInst Low) Source # 
Instance details

Defined in Language.JVM.ByteCode

type Rep (ByteCodeInst Low) = D1 (MetaData "ByteCodeInst" "Language.JVM.ByteCode" "jvm-binary-0.5.0-8tjUXfOvOFm5evlZ3bpMMl" False) (C1 (MetaCons "ByteCodeInst" PrefixI True) (S1 (MetaSel (Just "offset") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 ByteCodeOffset) :*: S1 (MetaSel (Just "opcode") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (ByteCodeOpr Low))))
type Rep (ByteCode Low) Source # 
Instance details

Defined in Language.JVM.ByteCode

type Rep (ByteCode Low) = D1 (MetaData "ByteCode" "Language.JVM.ByteCode" "jvm-binary-0.5.0-8tjUXfOvOFm5evlZ3bpMMl" False) (C1 (MetaCons "ByteCode" PrefixI True) (S1 (MetaSel (Just "byteCodeSize") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Word32) :*: S1 (MetaSel (Just "byteCodeInstructions") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 (Vector (ByteCodeInst Low)))))
type Rep (Attribute Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Base

type Rep (Attribute Low) = D1 (MetaData "Attribute" "Language.JVM.Attribute.Base" "jvm-binary-0.5.0-8tjUXfOvOFm5evlZ3bpMMl" False) (C1 (MetaCons "Attribute" PrefixI True) (S1 (MetaSel (Just "aName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Ref Text Low)) :*: S1 (MetaSel (Just "aInfo'") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 SizedByteString32)))
type Rep (VerificationTypeInfo Low) Source # 
Instance details

Defined in Language.JVM.Attribute.StackMapTable

type Rep (VerificationTypeInfo Low) = D1 (MetaData "VerificationTypeInfo" "Language.JVM.Attribute.StackMapTable" "jvm-binary-0.5.0-8tjUXfOvOFm5evlZ3bpMMl" False) (((C1 (MetaCons "VTTop" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "VTInteger" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "VTFloat" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "VTLong" PrefixI False) (U1 :: Type -> Type))) :+: ((C1 (MetaCons "VTDouble" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "VTNull" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "VTUninitializedThis" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "VTObject" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ref ClassName Low))) :+: C1 (MetaCons "VTUninitialized" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Word16))))))
type Rep (StackMapFrameType Low) Source # 
Instance details

Defined in Language.JVM.Attribute.StackMapTable

type Rep (StackMapFrame Low) Source # 
Instance details

Defined in Language.JVM.Attribute.StackMapTable

type Rep (StackMapFrame Low) = D1 (MetaData "StackMapFrame" "Language.JVM.Attribute.StackMapTable" "jvm-binary-0.5.0-8tjUXfOvOFm5evlZ3bpMMl" False) (C1 (MetaCons "StackMapFrame" PrefixI True) (S1 (MetaSel (Just "deltaOffset") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (DeltaOffset Low)) :*: S1 (MetaSel (Just "frameType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (StackMapFrameType Low))))
type Rep (StackMapTable Low) Source # 
Instance details

Defined in Language.JVM.Attribute.StackMapTable

type Rep (StackMapTable Low) = D1 (MetaData "StackMapTable" "Language.JVM.Attribute.StackMapTable" "jvm-binary-0.5.0-8tjUXfOvOFm5evlZ3bpMMl" True) (C1 (MetaCons "StackMapTable" PrefixI True) (S1 (MetaSel (Just "stackMapTable") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Choice (SizedList16 (StackMapFrame Low)) [StackMapFrame High] Low))))
type Rep (Signature Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Signature

type Rep (Signature Low) = D1 (MetaData "Signature" "Language.JVM.Attribute.Signature" "jvm-binary-0.5.0-8tjUXfOvOFm5evlZ3bpMMl" True) (C1 (MetaCons "Signature" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ref Text Low))))
type Rep (Exceptions Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Exceptions

type Rep (Exceptions Low) = D1 (MetaData "Exceptions" "Language.JVM.Attribute.Exceptions" "jvm-binary-0.5.0-8tjUXfOvOFm5evlZ3bpMMl" True) (C1 (MetaCons "Exceptions" PrefixI True) (S1 (MetaSel (Just "exceptions") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (SizedList16 (Ref ClassName Low)))))
type Rep (EnclosingMethod Low) Source # 
Instance details

Defined in Language.JVM.Attribute.EnclosingMethod

type Rep (EnclosingMethod Low) = D1 (MetaData "EnclosingMethod" "Language.JVM.Attribute.EnclosingMethod" "jvm-binary-0.5.0-8tjUXfOvOFm5evlZ3bpMMl" False) (C1 (MetaCons "EnclosingMethod" PrefixI True) (S1 (MetaSel (Just "enclosingClassName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Ref ClassName Low)) :*: S1 (MetaSel (Just "enclosingMethodName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Ref (Maybe MethodId) Low))))
type Rep (ConstantValue Low) Source # 
Instance details

Defined in Language.JVM.Attribute.ConstantValue

type Rep (ConstantValue Low) = D1 (MetaData "ConstantValue" "Language.JVM.Attribute.ConstantValue" "jvm-binary-0.5.0-8tjUXfOvOFm5evlZ3bpMMl" False) (C1 (MetaCons "ConstantValue" PrefixI True) (S1 (MetaSel (Just "constantValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Ref JValue Low))))
type Rep (CodeAttributes Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Code

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

Defined in Language.JVM.Attribute.Code

type Rep (Code Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Code

type Rep (BootstrapMethod Low) Source # 
Instance details

Defined in Language.JVM.Attribute.BootstrapMethods

type Rep (BootstrapMethod Low) = D1 (MetaData "BootstrapMethod" "Language.JVM.Attribute.BootstrapMethods" "jvm-binary-0.5.0-8tjUXfOvOFm5evlZ3bpMMl" False) (C1 (MetaCons "BootstrapMethod" PrefixI True) (S1 (MetaSel (Just "method") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (DeepRef MethodHandle Low)) :*: S1 (MetaSel (Just "arguments") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (SizedList16 (Ref JValue Low)))))
type Rep (BootstrapMethods Low) Source # 
Instance details

Defined in Language.JVM.Attribute.BootstrapMethods

type Rep (BootstrapMethods Low) = D1 (MetaData "BootstrapMethods" "Language.JVM.Attribute.BootstrapMethods" "jvm-binary-0.5.0-8tjUXfOvOFm5evlZ3bpMMl" True) (C1 (MetaCons "BootstrapMethods" PrefixI True) (S1 (MetaSel (Just "methods'") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (SizedList16 (BootstrapMethod Low)))))
type Rep (MethodAttributes Low) Source # 
Instance details

Defined in Language.JVM.Method

type Rep (MethodAttributes Low) = D1 (MetaData "MethodAttributes" "Language.JVM.Method" "jvm-binary-0.5.0-8tjUXfOvOFm5evlZ3bpMMl" False) (C1 (MetaCons "MethodAttributes" PrefixI True) ((S1 (MetaSel (Just "maCode") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Code Low]) :*: S1 (MetaSel (Just "maExceptions") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Exceptions Low])) :*: (S1 (MetaSel (Just "maSignatures") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Signature Low]) :*: S1 (MetaSel (Just "maOthers") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Attribute Low]))))
type Rep (Method Low) Source # 
Instance details

Defined in Language.JVM.Method

type Rep (FieldAttributes Low) Source # 
Instance details

Defined in Language.JVM.Field

type Rep (FieldAttributes Low) = D1 (MetaData "FieldAttributes" "Language.JVM.Field" "jvm-binary-0.5.0-8tjUXfOvOFm5evlZ3bpMMl" False) (C1 (MetaCons "FieldAttributes" PrefixI True) (S1 (MetaSel (Just "faConstantValues") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [ConstantValue Low]) :*: (S1 (MetaSel (Just "faSignatures") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Signature Low]) :*: S1 (MetaSel (Just "faOthers") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Attribute Low]))))
type Rep (Field Low) Source # 
Instance details

Defined in Language.JVM.Field

type Rep (InnerClass Low) Source # 
Instance details

Defined in Language.JVM.Attribute.InnerClasses

type Rep (InnerClass Low) = D1 (MetaData "InnerClass" "Language.JVM.Attribute.InnerClasses" "jvm-binary-0.5.0-8tjUXfOvOFm5evlZ3bpMMl" False) (C1 (MetaCons "InnerClass" PrefixI True) ((S1 (MetaSel (Just "icClassName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Ref ClassName Low)) :*: S1 (MetaSel (Just "icOuterClassName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Ref (Maybe ClassName) Low))) :*: (S1 (MetaSel (Just "icInnerName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Ref (Maybe Text) Low)) :*: S1 (MetaSel (Just "icInnerAccessFlags") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (BitSet16 ICAccessFlag)))))
type Rep (InnerClasses Low) Source # 
Instance details

Defined in Language.JVM.Attribute.InnerClasses

type Rep (InnerClasses Low) = D1 (MetaData "InnerClasses" "Language.JVM.Attribute.InnerClasses" "jvm-binary-0.5.0-8tjUXfOvOFm5evlZ3bpMMl" True) (C1 (MetaCons "InnerClasses" PrefixI True) (S1 (MetaSel (Just "innerClasses") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Choice (SizedList16 (InnerClass Low)) [InnerClass High] Low))))
type Rep (ClassAttributes Low) Source # 
Instance details

Defined in Language.JVM.ClassFile

type Rep (ClassFile Low) Source # 
Instance details

Defined in Language.JVM.ClassFile

type Rep (InClass FieldId Low) Source # 
Instance details

Defined in Language.JVM.Constant

type Rep (InClass FieldId Low) = D1 (MetaData "InClass" "Language.JVM.Constant" "jvm-binary-0.5.0-8tjUXfOvOFm5evlZ3bpMMl" False) (C1 (MetaCons "InClass" PrefixI True) (S1 (MetaSel (Just "inClassName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Ref ClassName Low)) :*: S1 (MetaSel (Just "inClassId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Ref FieldId Low))))
type Rep (InClass MethodId Low) Source # 
Instance details

Defined in Language.JVM.Constant

type Rep (InClass MethodId Low) = D1 (MetaData "InClass" "Language.JVM.Constant" "jvm-binary-0.5.0-8tjUXfOvOFm5evlZ3bpMMl" False) (C1 (MetaCons "InClass" PrefixI True) (S1 (MetaSel (Just "inClassName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Ref ClassName Low)) :*: S1 (MetaSel (Just "inClassId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Ref MethodId Low))))

data High Source #

Any data structure in the High stage, is easier to read.

Instances
Eq (InvokeDynamic High) Source # 
Instance details

Defined in Language.JVM.Constant

Eq (MethodHandleInterface High) Source # 
Instance details

Defined in Language.JVM.Constant

Eq (MethodHandleMethod High) Source # 
Instance details

Defined in Language.JVM.Constant

Eq (MethodHandleField High) Source # 
Instance details

Defined in Language.JVM.Constant

Eq (MethodHandle High) Source # 
Instance details

Defined in Language.JVM.Constant

Eq (AbsVariableMethodId High) Source # 
Instance details

Defined in Language.JVM.Constant

Eq (AbsInterfaceMethodId High) Source # 
Instance details

Defined in Language.JVM.Constant

Eq (Constant High) Source # 
Instance details

Defined in Language.JVM.Constant

Eq (ConstantPool High) Source # 
Instance details

Defined in Language.JVM.ConstantPool

Eq (ByteCodeOpr High) Source # 
Instance details

Defined in Language.JVM.ByteCode

Eq (SwitchTable High) Source # 
Instance details

Defined in Language.JVM.ByteCode

Eq (CConstant High) Source # 
Instance details

Defined in Language.JVM.ByteCode

Eq (Invocation High) Source # 
Instance details

Defined in Language.JVM.ByteCode

Eq (ByteCodeInst High) Source # 
Instance details

Defined in Language.JVM.ByteCode

Eq (ByteCode High) Source # 
Instance details

Defined in Language.JVM.ByteCode

Eq (Attribute High) Source # 
Instance details

Defined in Language.JVM.Attribute.Base

Eq (VerificationTypeInfo High) Source # 
Instance details

Defined in Language.JVM.Attribute.StackMapTable

Eq (StackMapFrameType High) Source # 
Instance details

Defined in Language.JVM.Attribute.StackMapTable

Eq (StackMapFrame High) Source # 
Instance details

Defined in Language.JVM.Attribute.StackMapTable

Eq (StackMapTable High) Source # 
Instance details

Defined in Language.JVM.Attribute.StackMapTable

Eq (Signature High) Source # 
Instance details

Defined in Language.JVM.Attribute.Signature

Eq (Exceptions High) Source # 
Instance details

Defined in Language.JVM.Attribute.Exceptions

Eq (EnclosingMethod High) Source # 
Instance details

Defined in Language.JVM.Attribute.EnclosingMethod

Eq (ConstantValue High) Source # 
Instance details

Defined in Language.JVM.Attribute.ConstantValue

Eq (CodeAttributes High) Source # 
Instance details

Defined in Language.JVM.Attribute.Code

Eq (ExceptionTable High) Source # 
Instance details

Defined in Language.JVM.Attribute.Code

Eq (Code High) Source # 
Instance details

Defined in Language.JVM.Attribute.Code

Methods

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

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

Eq (BootstrapMethod High) Source # 
Instance details

Defined in Language.JVM.Attribute.BootstrapMethods

Eq (BootstrapMethods High) Source # 
Instance details

Defined in Language.JVM.Attribute.BootstrapMethods

Eq (MethodAttributes High) Source # 
Instance details

Defined in Language.JVM.Method

Eq (Method High) Source # 
Instance details

Defined in Language.JVM.Method

Eq (FieldAttributes High) Source # 
Instance details

Defined in Language.JVM.Field

Eq (Field High) Source # 
Instance details

Defined in Language.JVM.Field

Methods

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

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

Eq (InnerClass High) Source # 
Instance details

Defined in Language.JVM.Attribute.InnerClasses

Eq (InnerClasses High) Source # 
Instance details

Defined in Language.JVM.Attribute.InnerClasses

Eq (ClassAttributes High) Source # 
Instance details

Defined in Language.JVM.ClassFile

Eq (ClassFile High) Source # 
Instance details

Defined in Language.JVM.ClassFile

Show (InvokeDynamic High) Source # 
Instance details

Defined in Language.JVM.Constant

Show (MethodHandleInterface High) Source # 
Instance details

Defined in Language.JVM.Constant

Show (MethodHandleMethod High) Source # 
Instance details

Defined in Language.JVM.Constant

Show (MethodHandleField High) Source # 
Instance details

Defined in Language.JVM.Constant

Show (MethodHandle High) Source # 
Instance details

Defined in Language.JVM.Constant

Show (AbsVariableMethodId High) Source # 
Instance details

Defined in Language.JVM.Constant

Show (AbsInterfaceMethodId High) Source # 
Instance details

Defined in Language.JVM.Constant

Show (Constant High) Source # 
Instance details

Defined in Language.JVM.Constant

Show (ConstantPool High) Source # 
Instance details

Defined in Language.JVM.ConstantPool

Show (ByteCodeOpr High) Source # 
Instance details

Defined in Language.JVM.ByteCode

Show (SwitchTable High) Source # 
Instance details

Defined in Language.JVM.ByteCode

Show (CConstant High) Source # 
Instance details

Defined in Language.JVM.ByteCode

Show (Invocation High) Source # 
Instance details

Defined in Language.JVM.ByteCode

Show (ByteCodeInst High) Source # 
Instance details

Defined in Language.JVM.ByteCode

Show (ByteCode High) Source # 
Instance details

Defined in Language.JVM.ByteCode

Show (Attribute High) Source # 
Instance details

Defined in Language.JVM.Attribute.Base

Show (VerificationTypeInfo High) Source # 
Instance details

Defined in Language.JVM.Attribute.StackMapTable

Show (StackMapFrameType High) Source # 
Instance details

Defined in Language.JVM.Attribute.StackMapTable

Show (StackMapFrame High) Source # 
Instance details

Defined in Language.JVM.Attribute.StackMapTable

Show (StackMapTable High) Source # 
Instance details

Defined in Language.JVM.Attribute.StackMapTable

Show (Signature High) Source # 
Instance details

Defined in Language.JVM.Attribute.Signature

Show (Exceptions High) Source # 
Instance details

Defined in Language.JVM.Attribute.Exceptions

Show (EnclosingMethod High) Source # 
Instance details

Defined in Language.JVM.Attribute.EnclosingMethod

Show (ConstantValue High) Source # 
Instance details

Defined in Language.JVM.Attribute.ConstantValue

Show (CodeAttributes High) Source # 
Instance details

Defined in Language.JVM.Attribute.Code

Show (ExceptionTable High) Source # 
Instance details

Defined in Language.JVM.Attribute.Code

Show (Code High) Source # 
Instance details

Defined in Language.JVM.Attribute.Code

Show (BootstrapMethod High) Source # 
Instance details

Defined in Language.JVM.Attribute.BootstrapMethods

Show (BootstrapMethods High) Source # 
Instance details

Defined in Language.JVM.Attribute.BootstrapMethods

Show (MethodAttributes High) Source # 
Instance details

Defined in Language.JVM.Method

Show (Method High) Source # 
Instance details

Defined in Language.JVM.Method

Show (FieldAttributes High) Source # 
Instance details

Defined in Language.JVM.Field

Show (Field High) Source # 
Instance details

Defined in Language.JVM.Field

Show (InnerClass High) Source # 
Instance details

Defined in Language.JVM.Attribute.InnerClasses

Show (InnerClasses High) Source # 
Instance details

Defined in Language.JVM.Attribute.InnerClasses

Show (ClassAttributes High) Source # 
Instance details

Defined in Language.JVM.ClassFile

Show (ClassFile High) Source # 
Instance details

Defined in Language.JVM.ClassFile

Generic (InvokeDynamic High) Source # 
Instance details

Defined in Language.JVM.Constant

Associated Types

type Rep (InvokeDynamic High) :: Type -> Type #

Generic (MethodHandleInterface High) Source # 
Instance details

Defined in Language.JVM.Constant

Associated Types

type Rep (MethodHandleInterface High) :: Type -> Type #

Generic (MethodHandleMethod High) Source # 
Instance details

Defined in Language.JVM.Constant

Associated Types

type Rep (MethodHandleMethod High) :: Type -> Type #

Generic (MethodHandleField High) Source # 
Instance details

Defined in Language.JVM.Constant

Associated Types

type Rep (MethodHandleField High) :: Type -> Type #

Generic (MethodHandle High) Source # 
Instance details

Defined in Language.JVM.Constant

Associated Types

type Rep (MethodHandle High) :: Type -> Type #

Generic (AbsVariableMethodId High) Source # 
Instance details

Defined in Language.JVM.Constant

Associated Types

type Rep (AbsVariableMethodId High) :: Type -> Type #

Generic (AbsInterfaceMethodId High) Source # 
Instance details

Defined in Language.JVM.Constant

Associated Types

type Rep (AbsInterfaceMethodId High) :: Type -> Type #

Generic (Constant High) Source # 
Instance details

Defined in Language.JVM.Constant

Associated Types

type Rep (Constant High) :: Type -> Type #

Generic (ConstantPool High) Source # 
Instance details

Defined in Language.JVM.ConstantPool

Associated Types

type Rep (ConstantPool High) :: Type -> Type #

Generic (ByteCodeOpr High) Source # 
Instance details

Defined in Language.JVM.ByteCode

Associated Types

type Rep (ByteCodeOpr High) :: Type -> Type #

Generic (SwitchTable High) Source # 
Instance details

Defined in Language.JVM.ByteCode

Associated Types

type Rep (SwitchTable High) :: Type -> Type #

Generic (CConstant High) Source # 
Instance details

Defined in Language.JVM.ByteCode

Associated Types

type Rep (CConstant High) :: Type -> Type #

Generic (Invocation High) Source # 
Instance details

Defined in Language.JVM.ByteCode

Associated Types

type Rep (Invocation High) :: Type -> Type #

Generic (ByteCodeInst High) Source # 
Instance details

Defined in Language.JVM.ByteCode

Associated Types

type Rep (ByteCodeInst High) :: Type -> Type #

Generic (ByteCode High) Source # 
Instance details

Defined in Language.JVM.ByteCode

Associated Types

type Rep (ByteCode High) :: Type -> Type #

Generic (Attribute High) Source # 
Instance details

Defined in Language.JVM.Attribute.Base

Associated Types

type Rep (Attribute High) :: Type -> Type #

Generic (VerificationTypeInfo High) Source # 
Instance details

Defined in Language.JVM.Attribute.StackMapTable

Associated Types

type Rep (VerificationTypeInfo High) :: Type -> Type #

Generic (StackMapFrameType High) Source # 
Instance details

Defined in Language.JVM.Attribute.StackMapTable

Associated Types

type Rep (StackMapFrameType High) :: Type -> Type #

Generic (StackMapFrame High) Source # 
Instance details

Defined in Language.JVM.Attribute.StackMapTable

Associated Types

type Rep (StackMapFrame High) :: Type -> Type #

Generic (StackMapTable High) Source # 
Instance details

Defined in Language.JVM.Attribute.StackMapTable

Associated Types

type Rep (StackMapTable High) :: Type -> Type #

Generic (Signature High) Source # 
Instance details

Defined in Language.JVM.Attribute.Signature

Associated Types

type Rep (Signature High) :: Type -> Type #

Generic (Exceptions High) Source # 
Instance details

Defined in Language.JVM.Attribute.Exceptions

Associated Types

type Rep (Exceptions High) :: Type -> Type #

Generic (EnclosingMethod High) Source # 
Instance details

Defined in Language.JVM.Attribute.EnclosingMethod

Associated Types

type Rep (EnclosingMethod High) :: Type -> Type #

Generic (ConstantValue High) Source # 
Instance details

Defined in Language.JVM.Attribute.ConstantValue

Associated Types

type Rep (ConstantValue High) :: Type -> Type #

Generic (CodeAttributes High) Source # 
Instance details

Defined in Language.JVM.Attribute.Code

Associated Types

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

Generic (ExceptionTable High) Source # 
Instance details

Defined in Language.JVM.Attribute.Code

Associated Types

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

Generic (Code High) Source # 
Instance details

Defined in Language.JVM.Attribute.Code

Associated Types

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

Methods

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

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

Generic (BootstrapMethod High) Source # 
Instance details

Defined in Language.JVM.Attribute.BootstrapMethods

Associated Types

type Rep (BootstrapMethod High) :: Type -> Type #

Generic (BootstrapMethods High) Source # 
Instance details

Defined in Language.JVM.Attribute.BootstrapMethods

Associated Types

type Rep (BootstrapMethods High) :: Type -> Type #

Generic (MethodAttributes High) Source # 
Instance details

Defined in Language.JVM.Method

Associated Types

type Rep (MethodAttributes High) :: Type -> Type #

Generic (Method High) Source # 
Instance details

Defined in Language.JVM.Method

Associated Types

type Rep (Method High) :: Type -> Type #

Methods

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

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

Generic (FieldAttributes High) Source # 
Instance details

Defined in Language.JVM.Field

Associated Types

type Rep (FieldAttributes High) :: Type -> Type #

Generic (Field High) Source # 
Instance details

Defined in Language.JVM.Field

Associated Types

type Rep (Field High) :: Type -> Type #

Methods

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

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

Generic (InnerClass High) Source # 
Instance details

Defined in Language.JVM.Attribute.InnerClasses

Associated Types

type Rep (InnerClass High) :: Type -> Type #

Generic (InnerClasses High) Source # 
Instance details

Defined in Language.JVM.Attribute.InnerClasses

Associated Types

type Rep (InnerClasses High) :: Type -> Type #

Generic (ClassAttributes High) Source # 
Instance details

Defined in Language.JVM.ClassFile

Associated Types

type Rep (ClassAttributes High) :: Type -> Type #

Generic (ClassFile High) Source # 
Instance details

Defined in Language.JVM.ClassFile

Associated Types

type Rep (ClassFile High) :: Type -> Type #

NFData (InvokeDynamic High) Source # 
Instance details

Defined in Language.JVM.Constant

Methods

rnf :: InvokeDynamic High -> () #

NFData (MethodHandleInterface High) Source # 
Instance details

Defined in Language.JVM.Constant

NFData (MethodHandleMethod High) Source # 
Instance details

Defined in Language.JVM.Constant

Methods

rnf :: MethodHandleMethod High -> () #

NFData (MethodHandleField High) Source # 
Instance details

Defined in Language.JVM.Constant

Methods

rnf :: MethodHandleField High -> () #

NFData (MethodHandle High) Source # 
Instance details

Defined in Language.JVM.Constant

Methods

rnf :: MethodHandle High -> () #

NFData (AbsVariableMethodId High) Source # 
Instance details

Defined in Language.JVM.Constant

Methods

rnf :: AbsVariableMethodId High -> () #

NFData (AbsInterfaceMethodId High) Source # 
Instance details

Defined in Language.JVM.Constant

Methods

rnf :: AbsInterfaceMethodId High -> () #

NFData (Constant High) Source # 
Instance details

Defined in Language.JVM.Constant

Methods

rnf :: Constant High -> () #

NFData (ConstantPool High) Source # 
Instance details

Defined in Language.JVM.ConstantPool

Methods

rnf :: ConstantPool High -> () #

NFData (ByteCodeOpr High) Source # 
Instance details

Defined in Language.JVM.ByteCode

Methods

rnf :: ByteCodeOpr High -> () #

NFData (SwitchTable High) Source # 
Instance details

Defined in Language.JVM.ByteCode

Methods

rnf :: SwitchTable High -> () #

NFData (CConstant High) Source # 
Instance details

Defined in Language.JVM.ByteCode

Methods

rnf :: CConstant High -> () #

NFData (Invocation High) Source # 
Instance details

Defined in Language.JVM.ByteCode

Methods

rnf :: Invocation High -> () #

NFData (ByteCodeInst High) Source # 
Instance details

Defined in Language.JVM.ByteCode

Methods

rnf :: ByteCodeInst High -> () #

NFData (ByteCode High) Source # 
Instance details

Defined in Language.JVM.ByteCode

Methods

rnf :: ByteCode High -> () #

NFData (Attribute High) Source # 
Instance details

Defined in Language.JVM.Attribute.Base

Methods

rnf :: Attribute High -> () #

NFData (VerificationTypeInfo High) Source # 
Instance details

Defined in Language.JVM.Attribute.StackMapTable

Methods

rnf :: VerificationTypeInfo High -> () #

NFData (StackMapFrameType High) Source # 
Instance details

Defined in Language.JVM.Attribute.StackMapTable

Methods

rnf :: StackMapFrameType High -> () #

NFData (StackMapFrame High) Source # 
Instance details

Defined in Language.JVM.Attribute.StackMapTable

Methods

rnf :: StackMapFrame High -> () #

NFData (StackMapTable High) Source # 
Instance details

Defined in Language.JVM.Attribute.StackMapTable

Methods

rnf :: StackMapTable High -> () #

NFData (Signature High) Source # 
Instance details

Defined in Language.JVM.Attribute.Signature

Methods

rnf :: Signature High -> () #

NFData (Exceptions High) Source # 
Instance details

Defined in Language.JVM.Attribute.Exceptions

Methods

rnf :: Exceptions High -> () #

NFData (EnclosingMethod High) Source # 
Instance details

Defined in Language.JVM.Attribute.EnclosingMethod

Methods

rnf :: EnclosingMethod High -> () #

NFData (ConstantValue High) Source # 
Instance details

Defined in Language.JVM.Attribute.ConstantValue

Methods

rnf :: ConstantValue High -> () #

NFData (CodeAttributes High) Source # 
Instance details

Defined in Language.JVM.Attribute.Code

Methods

rnf :: CodeAttributes High -> () #

NFData (ExceptionTable High) Source # 
Instance details

Defined in Language.JVM.Attribute.Code

Methods

rnf :: ExceptionTable High -> () #

NFData (Code High) Source # 
Instance details

Defined in Language.JVM.Attribute.Code

Methods

rnf :: Code High -> () #

NFData (BootstrapMethod High) Source # 
Instance details

Defined in Language.JVM.Attribute.BootstrapMethods

Methods

rnf :: BootstrapMethod High -> () #

NFData (BootstrapMethods High) Source # 
Instance details

Defined in Language.JVM.Attribute.BootstrapMethods

Methods

rnf :: BootstrapMethods High -> () #

NFData (MethodAttributes High) Source # 
Instance details

Defined in Language.JVM.Method

Methods

rnf :: MethodAttributes High -> () #

NFData (Method High) Source # 
Instance details

Defined in Language.JVM.Method

Methods

rnf :: Method High -> () #

NFData (FieldAttributes High) Source # 
Instance details

Defined in Language.JVM.Field

Methods

rnf :: FieldAttributes High -> () #

NFData (Field High) Source # 
Instance details

Defined in Language.JVM.Field

Methods

rnf :: Field High -> () #

NFData (InnerClass High) Source # 
Instance details

Defined in Language.JVM.Attribute.InnerClasses

Methods

rnf :: InnerClass High -> () #

NFData (InnerClasses High) Source # 
Instance details

Defined in Language.JVM.Attribute.InnerClasses

Methods

rnf :: InnerClasses High -> () #

NFData (ClassAttributes High) Source # 
Instance details

Defined in Language.JVM.ClassFile

Methods

rnf :: ClassAttributes High -> () #

NFData (ClassFile High) Source # 
Instance details

Defined in Language.JVM.ClassFile

Methods

rnf :: ClassFile High -> () #

Referenceable (InvokeDynamic High) Source # 
Instance details

Defined in Language.JVM.Constant

Methods

fromConst :: Monad m => (forall a'. String -> m a') -> Constant High -> m (InvokeDynamic High) Source #

toConst :: Monad m => InvokeDynamic High -> m (Constant High) Source #

Referenceable (MethodHandle High) Source # 
Instance details

Defined in Language.JVM.Constant

Methods

fromConst :: Monad m => (forall a'. String -> m a') -> Constant High -> m (MethodHandle High) Source #

toConst :: Monad m => MethodHandle High -> m (Constant High) Source #

Referenceable (AbsVariableMethodId High) Source # 
Instance details

Defined in Language.JVM.Constant

Referenceable (AbsInterfaceMethodId High) Source # 
Instance details

Defined in Language.JVM.Constant

Referenceable (Constant High) Source # 
Instance details

Defined in Language.JVM.Constant

Methods

fromConst :: Monad m => (forall a'. String -> m a') -> Constant High -> m (Constant High) Source #

toConst :: Monad m => Constant High -> m (Constant High) Source #

Eq (InClass FieldId High) Source # 
Instance details

Defined in Language.JVM.Constant

Eq (InClass MethodId High) Source # 
Instance details

Defined in Language.JVM.Constant

Show (InClass FieldId High) Source # 
Instance details

Defined in Language.JVM.Constant

Show (InClass MethodId High) Source # 
Instance details

Defined in Language.JVM.Constant

Generic (InClass FieldId High) Source # 
Instance details

Defined in Language.JVM.Constant

Associated Types

type Rep (InClass FieldId High) :: Type -> Type #

Generic (InClass MethodId High) Source # 
Instance details

Defined in Language.JVM.Constant

Associated Types

type Rep (InClass MethodId High) :: Type -> Type #

NFData (InClass FieldId High) Source # 
Instance details

Defined in Language.JVM.Constant

Methods

rnf :: InClass FieldId High -> () #

NFData (InClass MethodId High) Source # 
Instance details

Defined in Language.JVM.Constant

Methods

rnf :: InClass MethodId High -> () #

Referenceable (InClass FieldId High) Source # 
Instance details

Defined in Language.JVM.Constant

Methods

fromConst :: Monad m => (forall a'. String -> m a') -> Constant High -> m (InClass FieldId High) Source #

toConst :: Monad m => InClass FieldId High -> m (Constant High) Source #

Referenceable (InClass MethodId High) Source # 
Instance details

Defined in Language.JVM.Constant

Methods

fromConst :: Monad m => (forall a'. String -> m a') -> Constant High -> m (InClass MethodId High) Source #

toConst :: Monad m => InClass MethodId High -> m (Constant High) Source #

type Choice a b High Source # 
Instance details

Defined in Language.JVM.Stage

type Choice a b High = b
type Rep (InvokeDynamic High) Source # 
Instance details

Defined in Language.JVM.Constant

type Rep (InvokeDynamic High) = D1 (MetaData "InvokeDynamic" "Language.JVM.Constant" "jvm-binary-0.5.0-8tjUXfOvOFm5evlZ3bpMMl" False) (C1 (MetaCons "InvokeDynamic" PrefixI True) (S1 (MetaSel (Just "invokeDynamicAttrIndex") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Word16) :*: S1 (MetaSel (Just "invokeDynamicMethod") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Ref MethodId High))))
type Rep (MethodHandleInterface High) Source # 
Instance details

Defined in Language.JVM.Constant

type Rep (MethodHandleInterface High) = D1 (MetaData "MethodHandleInterface" "Language.JVM.Constant" "jvm-binary-0.5.0-8tjUXfOvOFm5evlZ3bpMMl" False) (C1 (MetaCons "MethodHandleInterface" PrefixI True) (S1 (MetaSel (Just "methodHandleInterfaceRef") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (DeepRef AbsInterfaceMethodId High))))
type Rep (MethodHandleMethod High) Source # 
Instance details

Defined in Language.JVM.Constant

type Rep (MethodHandleField High) Source # 
Instance details

Defined in Language.JVM.Constant

type Rep (MethodHandleField High) = D1 (MetaData "MethodHandleField" "Language.JVM.Constant" "jvm-binary-0.5.0-8tjUXfOvOFm5evlZ3bpMMl" False) (C1 (MetaCons "MethodHandleField" PrefixI True) (S1 (MetaSel (Just "methodHandleFieldKind") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 MethodHandleFieldKind) :*: S1 (MetaSel (Just "methodHandleFieldRef") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (DeepRef AbsFieldId High))))
type Rep (MethodHandle High) Source # 
Instance details

Defined in Language.JVM.Constant

type Rep (AbsVariableMethodId High) Source # 
Instance details

Defined in Language.JVM.Constant

type Rep (AbsVariableMethodId High) = D1 (MetaData "AbsVariableMethodId" "Language.JVM.Constant" "jvm-binary-0.5.0-8tjUXfOvOFm5evlZ3bpMMl" False) (C1 (MetaCons "AbsVariableMethodId" PrefixI True) (S1 (MetaSel (Just "variableIsInterface") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Bool) :*: S1 (MetaSel (Just "variableMethodId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (InClass MethodId High))))
type Rep (AbsInterfaceMethodId High) Source # 
Instance details

Defined in Language.JVM.Constant

type Rep (AbsInterfaceMethodId High) = D1 (MetaData "AbsInterfaceMethodId" "Language.JVM.Constant" "jvm-binary-0.5.0-8tjUXfOvOFm5evlZ3bpMMl" True) (C1 (MetaCons "AbsInterfaceMethodId" PrefixI True) (S1 (MetaSel (Just "interfaceMethodId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (InClass MethodId High))))
type Rep (Constant High) Source # 
Instance details

Defined in Language.JVM.Constant

type Rep (Constant High) = D1 (MetaData "Constant" "Language.JVM.Constant" "jvm-binary-0.5.0-8tjUXfOvOFm5evlZ3bpMMl" False) (((C1 (MetaCons "CString" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 SizedByteString16)) :+: (C1 (MetaCons "CInteger" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Int32)) :+: C1 (MetaCons "CFloat" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Float)))) :+: ((C1 (MetaCons "CLong" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Int64)) :+: C1 (MetaCons "CDouble" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Double))) :+: (C1 (MetaCons "CClassRef" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Ref Text High))) :+: C1 (MetaCons "CStringRef" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Ref ByteString High)))))) :+: ((C1 (MetaCons "CFieldRef" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (InClass FieldId High))) :+: (C1 (MetaCons "CMethodRef" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (InClass MethodId High))) :+: C1 (MetaCons "CInterfaceMethodRef" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (InClass MethodId High))))) :+: ((C1 (MetaCons "CNameAndType" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Ref Text High)) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Ref Text High))) :+: C1 (MetaCons "CMethodHandle" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (MethodHandle High)))) :+: (C1 (MetaCons "CMethodType" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Ref MethodDescriptor High))) :+: C1 (MetaCons "CInvokeDynamic" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (InvokeDynamic High)))))))
type Rep (ConstantPool High) Source # 
Instance details

Defined in Language.JVM.ConstantPool

type Rep (ConstantPool High) = D1 (MetaData "ConstantPool" "Language.JVM.ConstantPool" "jvm-binary-0.5.0-8tjUXfOvOFm5evlZ3bpMMl" True) (C1 (MetaCons "ConstantPool" PrefixI True) (S1 (MetaSel (Just "unConstantPool") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (IntMap (Constant High)))))
type Rep (ByteCodeOpr High) Source # 
Instance details

Defined in Language.JVM.ByteCode

type Rep (SwitchTable High) Source # 
Instance details

Defined in Language.JVM.ByteCode

type Rep (CConstant High) Source # 
Instance details

Defined in Language.JVM.ByteCode

type Rep (CConstant High) = D1 (MetaData "CConstant" "Language.JVM.ByteCode" "jvm-binary-0.5.0-8tjUXfOvOFm5evlZ3bpMMl" False) ((((C1 (MetaCons "CNull" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "CIntM1" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "CInt0" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "CInt1" PrefixI False) (U1 :: Type -> Type))) :+: ((C1 (MetaCons "CInt2" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "CInt3" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "CInt4" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "CInt5" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "CLong0" PrefixI False) (U1 :: Type -> Type))))) :+: (((C1 (MetaCons "CLong1" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "CFloat0" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "CFloat1" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "CFloat2" PrefixI False) (U1 :: Type -> Type))) :+: ((C1 (MetaCons "CDouble0" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "CDouble1" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "CByte" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Int8)) :+: (C1 (MetaCons "CShort" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Int16)) :+: C1 (MetaCons "CRef" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 (Maybe WordSize)) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 (Ref JValue High))))))))
type Rep (Invocation High) Source # 
Instance details

Defined in Language.JVM.ByteCode

type Rep (ByteCodeInst High) Source # 
Instance details

Defined in Language.JVM.ByteCode

type Rep (ByteCodeInst High) = D1 (MetaData "ByteCodeInst" "Language.JVM.ByteCode" "jvm-binary-0.5.0-8tjUXfOvOFm5evlZ3bpMMl" False) (C1 (MetaCons "ByteCodeInst" PrefixI True) (S1 (MetaSel (Just "offset") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 ByteCodeOffset) :*: S1 (MetaSel (Just "opcode") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (ByteCodeOpr High))))
type Rep (ByteCode High) Source # 
Instance details

Defined in Language.JVM.ByteCode

type Rep (ByteCode High) = D1 (MetaData "ByteCode" "Language.JVM.ByteCode" "jvm-binary-0.5.0-8tjUXfOvOFm5evlZ3bpMMl" False) (C1 (MetaCons "ByteCode" PrefixI True) (S1 (MetaSel (Just "byteCodeSize") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Word32) :*: S1 (MetaSel (Just "byteCodeInstructions") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 (Vector (ByteCodeInst High)))))
type Rep (Attribute High) Source # 
Instance details

Defined in Language.JVM.Attribute.Base

type Rep (Attribute High) = D1 (MetaData "Attribute" "Language.JVM.Attribute.Base" "jvm-binary-0.5.0-8tjUXfOvOFm5evlZ3bpMMl" False) (C1 (MetaCons "Attribute" PrefixI True) (S1 (MetaSel (Just "aName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Ref Text High)) :*: S1 (MetaSel (Just "aInfo'") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 SizedByteString32)))
type Rep (VerificationTypeInfo High) Source # 
Instance details

Defined in Language.JVM.Attribute.StackMapTable

type Rep (VerificationTypeInfo High) = D1 (MetaData "VerificationTypeInfo" "Language.JVM.Attribute.StackMapTable" "jvm-binary-0.5.0-8tjUXfOvOFm5evlZ3bpMMl" False) (((C1 (MetaCons "VTTop" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "VTInteger" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "VTFloat" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "VTLong" PrefixI False) (U1 :: Type -> Type))) :+: ((C1 (MetaCons "VTDouble" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "VTNull" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "VTUninitializedThis" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "VTObject" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ref ClassName High))) :+: C1 (MetaCons "VTUninitialized" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Word16))))))
type Rep (StackMapFrameType High) Source # 
Instance details

Defined in Language.JVM.Attribute.StackMapTable

type Rep (StackMapFrame High) Source # 
Instance details

Defined in Language.JVM.Attribute.StackMapTable

type Rep (StackMapFrame High) = D1 (MetaData "StackMapFrame" "Language.JVM.Attribute.StackMapTable" "jvm-binary-0.5.0-8tjUXfOvOFm5evlZ3bpMMl" False) (C1 (MetaCons "StackMapFrame" PrefixI True) (S1 (MetaSel (Just "deltaOffset") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (DeltaOffset High)) :*: S1 (MetaSel (Just "frameType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (StackMapFrameType High))))
type Rep (StackMapTable High) Source # 
Instance details

Defined in Language.JVM.Attribute.StackMapTable

type Rep (StackMapTable High) = D1 (MetaData "StackMapTable" "Language.JVM.Attribute.StackMapTable" "jvm-binary-0.5.0-8tjUXfOvOFm5evlZ3bpMMl" True) (C1 (MetaCons "StackMapTable" PrefixI True) (S1 (MetaSel (Just "stackMapTable") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Choice (SizedList16 (StackMapFrame Low)) [StackMapFrame High] High))))
type Rep (Signature High) Source # 
Instance details

Defined in Language.JVM.Attribute.Signature

type Rep (Signature High) = D1 (MetaData "Signature" "Language.JVM.Attribute.Signature" "jvm-binary-0.5.0-8tjUXfOvOFm5evlZ3bpMMl" True) (C1 (MetaCons "Signature" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ref Text High))))
type Rep (Exceptions High) Source # 
Instance details

Defined in Language.JVM.Attribute.Exceptions

type Rep (Exceptions High) = D1 (MetaData "Exceptions" "Language.JVM.Attribute.Exceptions" "jvm-binary-0.5.0-8tjUXfOvOFm5evlZ3bpMMl" True) (C1 (MetaCons "Exceptions" PrefixI True) (S1 (MetaSel (Just "exceptions") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (SizedList16 (Ref ClassName High)))))
type Rep (EnclosingMethod High) Source # 
Instance details

Defined in Language.JVM.Attribute.EnclosingMethod

type Rep (EnclosingMethod High) = D1 (MetaData "EnclosingMethod" "Language.JVM.Attribute.EnclosingMethod" "jvm-binary-0.5.0-8tjUXfOvOFm5evlZ3bpMMl" False) (C1 (MetaCons "EnclosingMethod" PrefixI True) (S1 (MetaSel (Just "enclosingClassName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Ref ClassName High)) :*: S1 (MetaSel (Just "enclosingMethodName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Ref (Maybe MethodId) High))))
type Rep (ConstantValue High) Source # 
Instance details

Defined in Language.JVM.Attribute.ConstantValue

type Rep (ConstantValue High) = D1 (MetaData "ConstantValue" "Language.JVM.Attribute.ConstantValue" "jvm-binary-0.5.0-8tjUXfOvOFm5evlZ3bpMMl" False) (C1 (MetaCons "ConstantValue" PrefixI True) (S1 (MetaSel (Just "constantValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Ref JValue High))))
type Rep (CodeAttributes High) Source # 
Instance details

Defined in Language.JVM.Attribute.Code

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

Defined in Language.JVM.Attribute.Code

type Rep (Code High) Source # 
Instance details

Defined in Language.JVM.Attribute.Code

type Rep (BootstrapMethod High) Source # 
Instance details

Defined in Language.JVM.Attribute.BootstrapMethods

type Rep (BootstrapMethod High) = D1 (MetaData "BootstrapMethod" "Language.JVM.Attribute.BootstrapMethods" "jvm-binary-0.5.0-8tjUXfOvOFm5evlZ3bpMMl" False) (C1 (MetaCons "BootstrapMethod" PrefixI True) (S1 (MetaSel (Just "method") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (DeepRef MethodHandle High)) :*: S1 (MetaSel (Just "arguments") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (SizedList16 (Ref JValue High)))))
type Rep (BootstrapMethods High) Source # 
Instance details

Defined in Language.JVM.Attribute.BootstrapMethods

type Rep (BootstrapMethods High) = D1 (MetaData "BootstrapMethods" "Language.JVM.Attribute.BootstrapMethods" "jvm-binary-0.5.0-8tjUXfOvOFm5evlZ3bpMMl" True) (C1 (MetaCons "BootstrapMethods" PrefixI True) (S1 (MetaSel (Just "methods'") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (SizedList16 (BootstrapMethod High)))))
type Rep (MethodAttributes High) Source # 
Instance details

Defined in Language.JVM.Method

type Rep (Method High) Source # 
Instance details

Defined in Language.JVM.Method

type Rep (FieldAttributes High) Source # 
Instance details

Defined in Language.JVM.Field

type Rep (FieldAttributes High) = D1 (MetaData "FieldAttributes" "Language.JVM.Field" "jvm-binary-0.5.0-8tjUXfOvOFm5evlZ3bpMMl" False) (C1 (MetaCons "FieldAttributes" PrefixI True) (S1 (MetaSel (Just "faConstantValues") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [ConstantValue High]) :*: (S1 (MetaSel (Just "faSignatures") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Signature High]) :*: S1 (MetaSel (Just "faOthers") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Attribute High]))))
type Rep (Field High) Source # 
Instance details

Defined in Language.JVM.Field

type Rep (InnerClass High) Source # 
Instance details

Defined in Language.JVM.Attribute.InnerClasses

type Rep (InnerClass High) = D1 (MetaData "InnerClass" "Language.JVM.Attribute.InnerClasses" "jvm-binary-0.5.0-8tjUXfOvOFm5evlZ3bpMMl" False) (C1 (MetaCons "InnerClass" PrefixI True) ((S1 (MetaSel (Just "icClassName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Ref ClassName High)) :*: S1 (MetaSel (Just "icOuterClassName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Ref (Maybe ClassName) High))) :*: (S1 (MetaSel (Just "icInnerName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Ref (Maybe Text) High)) :*: S1 (MetaSel (Just "icInnerAccessFlags") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (BitSet16 ICAccessFlag)))))
type Rep (InnerClasses High) Source # 
Instance details

Defined in Language.JVM.Attribute.InnerClasses

type Rep (InnerClasses High) = D1 (MetaData "InnerClasses" "Language.JVM.Attribute.InnerClasses" "jvm-binary-0.5.0-8tjUXfOvOFm5evlZ3bpMMl" True) (C1 (MetaCons "InnerClasses" PrefixI True) (S1 (MetaSel (Just "innerClasses") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Choice (SizedList16 (InnerClass Low)) [InnerClass High] High))))
type Rep (ClassAttributes High) Source # 
Instance details

Defined in Language.JVM.ClassFile

type Rep (ClassFile High) Source # 
Instance details

Defined in Language.JVM.ClassFile

type Rep (InClass FieldId High) Source # 
Instance details

Defined in Language.JVM.Constant

type Rep (InClass FieldId High) = D1 (MetaData "InClass" "Language.JVM.Constant" "jvm-binary-0.5.0-8tjUXfOvOFm5evlZ3bpMMl" False) (C1 (MetaCons "InClass" PrefixI True) (S1 (MetaSel (Just "inClassName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Ref ClassName High)) :*: S1 (MetaSel (Just "inClassId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Ref FieldId High))))
type Rep (InClass MethodId High) Source # 
Instance details

Defined in Language.JVM.Constant

type Rep (InClass MethodId High) = D1 (MetaData "InClass" "Language.JVM.Constant" "jvm-binary-0.5.0-8tjUXfOvOFm5evlZ3bpMMl" False) (C1 (MetaCons "InClass" PrefixI True) (S1 (MetaSel (Just "inClassName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Ref ClassName High)) :*: S1 (MetaSel (Just "inClassId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Ref MethodId High))))

type Ref v r = Choice Index v r Source #

A reference is a choice between an index and a value.

type Index = Word16 Source #

An index into the constant pool.

type DeepRef v r = Ref (v r) r Source #

A deep reference points to something that itself is staged.

type family Choice a b r Source #

The basic part of the stage system is the choice. The Choice chooses between two types depending on the stage.

Instances
type Choice a b Low Source # 
Instance details

Defined in Language.JVM.Stage

type Choice a b Low = a
type Choice a b High Source # 
Instance details

Defined in Language.JVM.Stage

type Choice a b High = b