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

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

Language.JVM.Constant

Contents

Description

This module contains the Constant type and the ConstantPool. These are essential for accessing data in the class-file.

Synopsis

Documentation

data Constant r Source #

A constant is a multi word item in the ConstantPool. Each of the constructors are pretty much self-explanatory from the types.

Instances

Staged Constant Source # 

Methods

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

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

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

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

Associated Types

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

Generic (Constant Low) Source # 

Associated Types

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

Methods

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

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

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

Methods

rnf :: Constant High -> () #

NFData (Constant Low) Source # 

Methods

rnf :: Constant Low -> () #

Referenceable (Constant High) Source # 

Methods

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

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

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

constantSize :: Constant r -> Int Source #

Some of the Constants take up more space in the constant pool than other. Notice that String and MethodType is not of size 32, but is still awarded value 1. This is due to an inconsistency in JVM.

typeToStr :: Constant r -> String Source #

Hack that returns the name of a constant.

class Referenceable a where Source #

Referenceable is something that can exist in the constant pool.

Minimal complete definition

fromConst, toConst

Methods

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

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

Instances

Referenceable ByteString Source # 

Methods

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

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

Referenceable Text Source # 

Methods

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

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

Referenceable FieldDescriptor Source # 

Methods

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

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

Referenceable MethodDescriptor Source # 

Methods

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

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

Referenceable ClassName Source # 

Methods

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

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

Referenceable FieldId Source # 

Methods

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

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

Referenceable MethodId Source # 

Methods

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

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

Referenceable JValue Source # 

Methods

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

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

TypeParse a => Referenceable (NameAndType a) Source # 

Methods

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

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

Referenceable (InvokeDynamic High) Source # 

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 # 

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 # 
Referenceable (AbsInterfaceMethodId High) Source # 
Referenceable (Constant High) Source # 

Methods

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

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

Referenceable (InClass FieldId High) Source # 

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 # 

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 #

data JValue Source #

A constant pool value in java

Instances

Eq JValue Source # 

Methods

(==) :: JValue -> JValue -> Bool #

(/=) :: JValue -> JValue -> Bool #

Show JValue Source # 
Generic JValue Source # 

Associated Types

type Rep JValue :: * -> * #

Methods

from :: JValue -> Rep JValue x #

to :: Rep JValue x -> JValue #

NFData JValue Source # 

Methods

rnf :: JValue -> () #

Referenceable JValue Source # 

Methods

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

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

type Rep JValue Source # 

Special constants

newtype ClassName Source #

A class name

Constructors

ClassName 

Instances

data InClass a r Source #

Anything pointing inside a class

Constructors

InClass 

Fields

Instances

Referenceable r => Staged (InClass r) Source # 

Methods

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

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

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

Eq (InClass FieldId High) Source # 
Eq (InClass FieldId Low) Source # 
Eq (InClass MethodId High) Source # 
Eq (InClass MethodId Low) Source # 
Ord (InClass FieldId Low) Source # 
Ord (InClass MethodId Low) Source # 
Show (InClass FieldId High) Source # 
Show (InClass FieldId Low) Source # 
Show (InClass MethodId High) Source # 
Show (InClass MethodId Low) Source # 
Generic (InClass FieldId High) Source # 

Associated Types

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

Generic (InClass FieldId Low) Source # 

Associated Types

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

Generic (InClass MethodId High) Source # 

Associated Types

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

Generic (InClass MethodId Low) Source # 

Associated Types

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

Binary (InClass FieldId Low) Source # 
Binary (InClass MethodId Low) Source # 
NFData (InClass FieldId High) Source # 

Methods

rnf :: InClass FieldId High -> () #

NFData (InClass FieldId Low) Source # 

Methods

rnf :: InClass FieldId Low -> () #

NFData (InClass MethodId High) Source # 

Methods

rnf :: InClass MethodId High -> () #

NFData (InClass MethodId Low) Source # 

Methods

rnf :: InClass MethodId Low -> () #

Referenceable (InClass FieldId High) Source # 

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 # 

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 Rep (InClass FieldId High) Source # 
type Rep (InClass FieldId High) = D1 * (MetaData "InClass" "Language.JVM.Constant" "jvm-binary-0.1.0-JJ8Rr7ERir79pQaBJvdiXV" False) (C1 * (MetaCons "InClass" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "inClassName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Ref ClassName High))) (S1 * (MetaSel (Just Symbol "inClassId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Ref FieldId High)))))
type Rep (InClass FieldId Low) Source # 
type Rep (InClass FieldId Low) = D1 * (MetaData "InClass" "Language.JVM.Constant" "jvm-binary-0.1.0-JJ8Rr7ERir79pQaBJvdiXV" False) (C1 * (MetaCons "InClass" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "inClassName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Ref ClassName Low))) (S1 * (MetaSel (Just Symbol "inClassId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Ref FieldId Low)))))
type Rep (InClass MethodId High) Source # 
type Rep (InClass MethodId High) = D1 * (MetaData "InClass" "Language.JVM.Constant" "jvm-binary-0.1.0-JJ8Rr7ERir79pQaBJvdiXV" False) (C1 * (MetaCons "InClass" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "inClassName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Ref ClassName High))) (S1 * (MetaSel (Just Symbol "inClassId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Ref MethodId High)))))
type Rep (InClass MethodId Low) Source # 
type Rep (InClass MethodId Low) = D1 * (MetaData "InClass" "Language.JVM.Constant" "jvm-binary-0.1.0-JJ8Rr7ERir79pQaBJvdiXV" False) (C1 * (MetaCons "InClass" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "inClassName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Ref ClassName Low))) (S1 * (MetaSel (Just Symbol "inClassId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Ref MethodId Low)))))

type AbsMethodId = InClass MethodId Source #

A method id in a class.

type AbsFieldId = InClass FieldId Source #

A field id in a class

newtype AbsInterfaceMethodId r Source #

An interface method, which is a class in a method.

Instances

Eq (AbsInterfaceMethodId High) Source # 
Eq (AbsInterfaceMethodId Low) Source # 
Ord (AbsInterfaceMethodId Low) Source # 
Show (AbsInterfaceMethodId High) Source # 
Show (AbsInterfaceMethodId Low) Source # 
Generic (AbsInterfaceMethodId High) Source # 
Generic (AbsInterfaceMethodId Low) Source # 
Binary (AbsInterfaceMethodId Low) Source # 
NFData (AbsInterfaceMethodId High) Source # 

Methods

rnf :: AbsInterfaceMethodId High -> () #

NFData (AbsInterfaceMethodId Low) Source # 

Methods

rnf :: AbsInterfaceMethodId Low -> () #

Referenceable (AbsInterfaceMethodId High) Source # 
type Rep (AbsInterfaceMethodId High) Source # 
type Rep (AbsInterfaceMethodId High) = D1 * (MetaData "AbsInterfaceMethodId" "Language.JVM.Constant" "jvm-binary-0.1.0-JJ8Rr7ERir79pQaBJvdiXV" True) (C1 * (MetaCons "AbsInterfaceMethodId" PrefixI True) (S1 * (MetaSel (Just Symbol "interfaceMethodId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (InClass MethodId High))))
type Rep (AbsInterfaceMethodId Low) Source # 
type Rep (AbsInterfaceMethodId Low) = D1 * (MetaData "AbsInterfaceMethodId" "Language.JVM.Constant" "jvm-binary-0.1.0-JJ8Rr7ERir79pQaBJvdiXV" True) (C1 * (MetaCons "AbsInterfaceMethodId" PrefixI True) (S1 * (MetaSel (Just Symbol "interfaceMethodId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (InClass MethodId Low))))

data AbsVariableMethodId r Source #

In some cases we can both point to interface methods and regular methods.

Instances

Eq (AbsVariableMethodId High) Source # 
Eq (AbsVariableMethodId Low) Source # 
Ord (AbsVariableMethodId Low) Source # 
Show (AbsVariableMethodId High) Source # 
Show (AbsVariableMethodId Low) Source # 
Generic (AbsVariableMethodId High) Source # 
Generic (AbsVariableMethodId Low) Source # 
Binary (AbsVariableMethodId Low) Source # 
NFData (AbsVariableMethodId High) Source # 

Methods

rnf :: AbsVariableMethodId High -> () #

NFData (AbsVariableMethodId Low) Source # 

Methods

rnf :: AbsVariableMethodId Low -> () #

Referenceable (AbsVariableMethodId High) Source # 
type Rep (AbsVariableMethodId High) Source # 
type Rep (AbsVariableMethodId High) = D1 * (MetaData "AbsVariableMethodId" "Language.JVM.Constant" "jvm-binary-0.1.0-JJ8Rr7ERir79pQaBJvdiXV" False) ((:+:) * (C1 * (MetaCons "VInterfaceMethodId" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (AbsInterfaceMethodId High)))) (C1 * (MetaCons "VMethodId" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (AbsMethodId High)))))
type Rep (AbsVariableMethodId Low) Source # 
type Rep (AbsVariableMethodId Low) = D1 * (MetaData "AbsVariableMethodId" "Language.JVM.Constant" "jvm-binary-0.1.0-JJ8Rr7ERir79pQaBJvdiXV" False) ((:+:) * (C1 * (MetaCons "VInterfaceMethodId" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (AbsInterfaceMethodId Low)))) (C1 * (MetaCons "VMethodId" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (AbsMethodId Low)))))

newtype MethodId Source #

Instances

Eq MethodId Source # 
Ord MethodId Source # 
Show MethodId Source # 
IsString MethodId Source # 
Generic MethodId Source # 

Associated Types

type Rep MethodId :: * -> * #

Methods

from :: MethodId -> Rep MethodId x #

to :: Rep MethodId x -> MethodId #

NFData MethodId Source # 

Methods

rnf :: MethodId -> () #

Referenceable MethodId Source # 

Methods

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

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

Eq (InClass MethodId High) Source # 
Eq (InClass MethodId Low) Source # 
Ord (InClass MethodId Low) Source # 
Show (InClass MethodId High) Source # 
Show (InClass MethodId Low) Source # 
Generic (InClass MethodId High) Source # 

Associated Types

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

Generic (InClass MethodId Low) Source # 

Associated Types

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

Binary (InClass MethodId Low) Source # 
NFData (InClass MethodId High) Source # 

Methods

rnf :: InClass MethodId High -> () #

NFData (InClass MethodId Low) Source # 

Methods

rnf :: InClass MethodId Low -> () #

Referenceable (InClass MethodId High) Source # 

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 Rep MethodId Source # 
type Rep MethodId = D1 * (MetaData "MethodId" "Language.JVM.Constant" "jvm-binary-0.1.0-JJ8Rr7ERir79pQaBJvdiXV" True) (C1 * (MetaCons "MethodId" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (NameAndType MethodDescriptor))))
type Rep (InClass MethodId High) Source # 
type Rep (InClass MethodId High) = D1 * (MetaData "InClass" "Language.JVM.Constant" "jvm-binary-0.1.0-JJ8Rr7ERir79pQaBJvdiXV" False) (C1 * (MetaCons "InClass" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "inClassName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Ref ClassName High))) (S1 * (MetaSel (Just Symbol "inClassId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Ref MethodId High)))))
type Rep (InClass MethodId Low) Source # 
type Rep (InClass MethodId Low) = D1 * (MetaData "InClass" "Language.JVM.Constant" "jvm-binary-0.1.0-JJ8Rr7ERir79pQaBJvdiXV" False) (C1 * (MetaCons "InClass" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "inClassName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Ref ClassName Low))) (S1 * (MetaSel (Just Symbol "inClassId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Ref MethodId Low)))))

newtype FieldId Source #

Instances

Eq FieldId Source # 

Methods

(==) :: FieldId -> FieldId -> Bool #

(/=) :: FieldId -> FieldId -> Bool #

Ord FieldId Source # 
Show FieldId Source # 
IsString FieldId Source # 

Methods

fromString :: String -> FieldId #

Generic FieldId Source # 

Associated Types

type Rep FieldId :: * -> * #

Methods

from :: FieldId -> Rep FieldId x #

to :: Rep FieldId x -> FieldId #

NFData FieldId Source # 

Methods

rnf :: FieldId -> () #

Referenceable FieldId Source # 

Methods

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

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

Eq (InClass FieldId High) Source # 
Eq (InClass FieldId Low) Source # 
Ord (InClass FieldId Low) Source # 
Show (InClass FieldId High) Source # 
Show (InClass FieldId Low) Source # 
Generic (InClass FieldId High) Source # 

Associated Types

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

Generic (InClass FieldId Low) Source # 

Associated Types

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

Binary (InClass FieldId Low) Source # 
NFData (InClass FieldId High) Source # 

Methods

rnf :: InClass FieldId High -> () #

NFData (InClass FieldId Low) Source # 

Methods

rnf :: InClass FieldId Low -> () #

Referenceable (InClass FieldId High) Source # 

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 #

type Rep FieldId Source # 
type Rep FieldId = D1 * (MetaData "FieldId" "Language.JVM.Constant" "jvm-binary-0.1.0-JJ8Rr7ERir79pQaBJvdiXV" True) (C1 * (MetaCons "FieldId" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (NameAndType FieldDescriptor))))
type Rep (InClass FieldId High) Source # 
type Rep (InClass FieldId High) = D1 * (MetaData "InClass" "Language.JVM.Constant" "jvm-binary-0.1.0-JJ8Rr7ERir79pQaBJvdiXV" False) (C1 * (MetaCons "InClass" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "inClassName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Ref ClassName High))) (S1 * (MetaSel (Just Symbol "inClassId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Ref FieldId High)))))
type Rep (InClass FieldId Low) Source # 
type Rep (InClass FieldId Low) = D1 * (MetaData "InClass" "Language.JVM.Constant" "jvm-binary-0.1.0-JJ8Rr7ERir79pQaBJvdiXV" False) (C1 * (MetaCons "InClass" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "inClassName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Ref ClassName Low))) (S1 * (MetaSel (Just Symbol "inClassId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Ref FieldId Low)))))

data NameAndType a Source #

A name and a type

Constructors

NameAndType 

Fields

Instances

Eq a => Eq (NameAndType a) Source # 
Ord a => Ord (NameAndType a) Source # 
Show a => Show (NameAndType a) Source # 
TypeParse t => IsString (NameAndType t) Source # 
Generic (NameAndType a) Source # 

Associated Types

type Rep (NameAndType a) :: * -> * #

Methods

from :: NameAndType a -> Rep (NameAndType a) x #

to :: Rep (NameAndType a) x -> NameAndType a #

NFData a => NFData (NameAndType a) Source # 

Methods

rnf :: NameAndType a -> () #

TypeParse t => TypeParse (NameAndType t) Source # 
TypeParse a => Referenceable (NameAndType a) Source # 

Methods

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

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

type Rep (NameAndType a) Source # 
type Rep (NameAndType a) = D1 * (MetaData "NameAndType" "Language.JVM.Type" "jvm-binary-0.1.0-JJ8Rr7ERir79pQaBJvdiXV" False) (C1 * (MetaCons "NameAndType" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "ntName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Text)) (S1 * (MetaSel (Just Symbol "ntDescriptor") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * a))))

data MethodDescriptor Source #

Method Descriptor

Instances

Eq MethodDescriptor Source # 
Ord MethodDescriptor Source # 
Show MethodDescriptor Source # 
IsString MethodDescriptor Source # 
Generic MethodDescriptor Source # 
NFData MethodDescriptor Source # 

Methods

rnf :: MethodDescriptor -> () #

TypeParse MethodDescriptor Source # 
Referenceable MethodDescriptor Source # 

Methods

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

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

type Rep MethodDescriptor Source # 
type Rep MethodDescriptor = D1 * (MetaData "MethodDescriptor" "Language.JVM.Type" "jvm-binary-0.1.0-JJ8Rr7ERir79pQaBJvdiXV" False) (C1 * (MetaCons "MethodDescriptor" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "methodDescriptorArguments") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [JType])) (S1 * (MetaSel (Just Symbol "methodDescriptorReturnType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe JType)))))

data FieldDescriptor Source #

Field Descriptor

Instances

Eq FieldDescriptor Source # 
Ord FieldDescriptor Source # 
Show FieldDescriptor Source # 
IsString FieldDescriptor Source # 
Generic FieldDescriptor Source # 
NFData FieldDescriptor Source # 

Methods

rnf :: FieldDescriptor -> () #

TypeParse FieldDescriptor Source # 
Referenceable FieldDescriptor Source # 

Methods

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

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

type Rep FieldDescriptor Source # 
type Rep FieldDescriptor = D1 * (MetaData "FieldDescriptor" "Language.JVM.Type" "jvm-binary-0.1.0-JJ8Rr7ERir79pQaBJvdiXV" True) (C1 * (MetaCons "FieldDescriptor" PrefixI True) (S1 * (MetaSel (Just Symbol "fieldDescriptorType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * JType)))

data MethodHandle r Source #

The union type over the different method handles.

Instances

Staged MethodHandle Source # 

Methods

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

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

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

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

Associated Types

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

Generic (MethodHandle Low) Source # 

Associated Types

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

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

Methods

rnf :: MethodHandle High -> () #

NFData (MethodHandle Low) Source # 

Methods

rnf :: MethodHandle Low -> () #

Referenceable (MethodHandle High) Source # 

Methods

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

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

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

data MethodHandleField r Source #

Instances

Staged MethodHandleField Source # 

Methods

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

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

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

Eq (MethodHandleField High) Source # 
Eq (MethodHandleField Low) Source # 
Ord (MethodHandleField Low) Source # 
Show (MethodHandleField High) Source # 
Show (MethodHandleField Low) Source # 
Generic (MethodHandleField High) Source # 
Generic (MethodHandleField Low) Source # 
NFData (MethodHandleField High) Source # 

Methods

rnf :: MethodHandleField High -> () #

NFData (MethodHandleField Low) Source # 

Methods

rnf :: MethodHandleField Low -> () #

type Rep (MethodHandleField High) Source # 
type Rep (MethodHandleField High) = D1 * (MetaData "MethodHandleField" "Language.JVM.Constant" "jvm-binary-0.1.0-JJ8Rr7ERir79pQaBJvdiXV" False) (C1 * (MetaCons "MethodHandleField" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "methodHandleFieldKind") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * MethodHandleFieldKind)) (S1 * (MetaSel (Just Symbol "methodHandleFieldRef") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (DeepRef AbsFieldId High)))))
type Rep (MethodHandleField Low) Source # 
type Rep (MethodHandleField Low) = D1 * (MetaData "MethodHandleField" "Language.JVM.Constant" "jvm-binary-0.1.0-JJ8Rr7ERir79pQaBJvdiXV" False) (C1 * (MetaCons "MethodHandleField" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "methodHandleFieldKind") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * MethodHandleFieldKind)) (S1 * (MetaSel (Just Symbol "methodHandleFieldRef") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (DeepRef AbsFieldId Low)))))

data MethodHandleMethod r Source #

Instances

Staged MethodHandleMethod Source # 

Methods

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

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

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

Eq (MethodHandleMethod High) Source # 
Eq (MethodHandleMethod Low) Source # 
Ord (MethodHandleMethod Low) Source # 
Show (MethodHandleMethod High) Source # 
Show (MethodHandleMethod Low) Source # 
Generic (MethodHandleMethod High) Source # 
Generic (MethodHandleMethod Low) Source # 
NFData (MethodHandleMethod High) Source # 

Methods

rnf :: MethodHandleMethod High -> () #

NFData (MethodHandleMethod Low) Source # 

Methods

rnf :: MethodHandleMethod Low -> () #

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

data MethodHandleInterface r Source #

Instances

Staged MethodHandleInterface Source # 
Eq (MethodHandleInterface High) Source # 
Eq (MethodHandleInterface Low) Source # 
Ord (MethodHandleInterface Low) Source # 
Show (MethodHandleInterface High) Source # 
Show (MethodHandleInterface Low) Source # 
Generic (MethodHandleInterface High) Source # 
Generic (MethodHandleInterface Low) Source # 
NFData (MethodHandleInterface High) Source # 
NFData (MethodHandleInterface Low) Source # 

Methods

rnf :: MethodHandleInterface Low -> () #

type Rep (MethodHandleInterface High) Source # 
type Rep (MethodHandleInterface High) = D1 * (MetaData "MethodHandleInterface" "Language.JVM.Constant" "jvm-binary-0.1.0-JJ8Rr7ERir79pQaBJvdiXV" False) (C1 * (MetaCons "MethodHandleInterface" PrefixI True) (S1 * (MetaSel (Just Symbol "methodHandleInterfaceRef") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (DeepRef AbsInterfaceMethodId High))))
type Rep (MethodHandleInterface Low) Source # 
type Rep (MethodHandleInterface Low) = D1 * (MetaData "MethodHandleInterface" "Language.JVM.Constant" "jvm-binary-0.1.0-JJ8Rr7ERir79pQaBJvdiXV" False) (C1 * (MetaCons "MethodHandleInterface" PrefixI True) (S1 * (MetaSel (Just Symbol "methodHandleInterfaceRef") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (DeepRef AbsInterfaceMethodId Low))))

data MethodHandleFieldKind Source #

Instances

Eq MethodHandleFieldKind Source # 
Ord MethodHandleFieldKind Source # 
Show MethodHandleFieldKind Source # 
Generic MethodHandleFieldKind Source # 
NFData MethodHandleFieldKind Source # 

Methods

rnf :: MethodHandleFieldKind -> () #

type Rep MethodHandleFieldKind Source # 
type Rep MethodHandleFieldKind = D1 * (MetaData "MethodHandleFieldKind" "Language.JVM.Constant" "jvm-binary-0.1.0-JJ8Rr7ERir79pQaBJvdiXV" False) ((:+:) * ((:+:) * (C1 * (MetaCons "MHGetField" PrefixI False) (U1 *)) (C1 * (MetaCons "MHGetStatic" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "MHPutField" PrefixI False) (U1 *)) (C1 * (MetaCons "MHPutStatic" PrefixI False) (U1 *))))

data InvokeDynamic r Source #

Instances

Staged InvokeDynamic Source # 

Methods

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

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

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

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

Associated Types

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

Generic (InvokeDynamic Low) Source # 

Associated Types

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

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

Methods

rnf :: InvokeDynamic High -> () #

NFData (InvokeDynamic Low) Source # 

Methods

rnf :: InvokeDynamic Low -> () #

Referenceable (InvokeDynamic High) Source # 

Methods

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

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

type Rep (InvokeDynamic High) Source # 
type Rep (InvokeDynamic High) = D1 * (MetaData "InvokeDynamic" "Language.JVM.Constant" "jvm-binary-0.1.0-JJ8Rr7ERir79pQaBJvdiXV" False) (C1 * (MetaCons "InvokeDynamic" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "invokeDynamicAttrIndex") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Word16)) (S1 * (MetaSel (Just Symbol "invokeDynamicMethod") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Ref MethodId High)))))
type Rep (InvokeDynamic Low) Source # 
type Rep (InvokeDynamic Low) = D1 * (MetaData "InvokeDynamic" "Language.JVM.Constant" "jvm-binary-0.1.0-JJ8Rr7ERir79pQaBJvdiXV" False) (C1 * (MetaCons "InvokeDynamic" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "invokeDynamicAttrIndex") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Word16)) (S1 * (MetaSel (Just Symbol "invokeDynamicMethod") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Ref MethodId Low)))))

re-exports

data High Source #

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

Instances

Eq (InvokeDynamic High) # 
Eq (MethodHandleInterface High) # 
Eq (MethodHandleMethod High) # 
Eq (MethodHandleField High) # 
Eq (MethodHandle High) # 
Eq (AbsVariableMethodId High) # 
Eq (AbsInterfaceMethodId High) # 
Eq (Constant High) # 
Eq (ConstantPool High) # 
Eq (ByteCodeOpr High) # 
Eq (SwitchTable High) # 
Eq (CConstant High) # 
Eq (Invocation High) # 
Eq (ExactArrayType High) # 
Eq (ByteCodeInst High) # 
Eq (ByteCode High) # 
Eq (Attribute High) # 
Eq (VerificationTypeInfo High) # 
Eq (StackMapFrameType High) # 
Eq (StackMapFrame High) # 
Eq (StackMapTable High) # 
Eq (Signature High) # 
Eq (Exceptions High) # 
Eq (ConstantValue High) # 
Eq (CodeAttributes High) # 
Eq (ExceptionTable High) # 
Eq (Code High) # 

Methods

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

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

Eq (BootstrapMethod High) # 
Eq (BootstrapMethods High) # 
Eq (MethodAttributes High) # 
Eq (Method High) # 
Eq (FieldAttributes High) # 
Eq (Field High) # 

Methods

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

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

Eq (ClassAttributes High) # 
Eq (ClassFile High) # 
Show (InvokeDynamic High) # 
Show (MethodHandleInterface High) # 
Show (MethodHandleMethod High) # 
Show (MethodHandleField High) # 
Show (MethodHandle High) # 
Show (AbsVariableMethodId High) # 
Show (AbsInterfaceMethodId High) # 
Show (Constant High) # 
Show (ConstantPool High) # 
Show (ByteCodeOpr High) # 
Show (SwitchTable High) # 
Show (CConstant High) # 
Show (Invocation High) # 
Show (ExactArrayType High) # 
Show (ByteCodeInst High) # 
Show (ByteCode High) # 
Show (Attribute High) # 
Show (VerificationTypeInfo High) # 
Show (StackMapFrameType High) # 
Show (StackMapFrame High) # 
Show (StackMapTable High) # 
Show (Signature High) # 
Show (Exceptions High) # 
Show (ConstantValue High) # 
Show (CodeAttributes High) # 
Show (ExceptionTable High) # 
Show (Code High) # 
Show (BootstrapMethod High) # 
Show (BootstrapMethods High) # 
Show (MethodAttributes High) # 
Show (Method High) # 
Show (FieldAttributes High) # 
Show (Field High) # 
Show (ClassAttributes High) # 
Show (ClassFile High) # 
Generic (InvokeDynamic High) # 

Associated Types

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

Generic (MethodHandleInterface High) # 
Generic (MethodHandleMethod High) # 
Generic (MethodHandleField High) # 
Generic (MethodHandle High) # 

Associated Types

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

Generic (AbsVariableMethodId High) # 
Generic (AbsInterfaceMethodId High) # 
Generic (Constant High) # 

Associated Types

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

Generic (ConstantPool High) # 

Associated Types

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

Generic (ByteCodeOpr High) # 

Associated Types

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

Generic (SwitchTable High) # 

Associated Types

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

Generic (CConstant High) # 

Associated Types

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

Generic (Invocation High) # 

Associated Types

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

Generic (ExactArrayType High) # 

Associated Types

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

Generic (ByteCodeInst High) # 

Associated Types

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

Generic (ByteCode High) # 

Associated Types

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

Generic (Attribute High) # 

Associated Types

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

Generic (VerificationTypeInfo High) # 
Generic (StackMapFrameType High) # 
Generic (StackMapFrame High) # 

Associated Types

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

Generic (StackMapTable High) # 

Associated Types

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

Generic (Signature High) # 

Associated Types

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

Generic (Exceptions High) # 

Associated Types

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

Generic (ConstantValue High) # 

Associated Types

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

Generic (CodeAttributes High) # 

Associated Types

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

Generic (ExceptionTable High) # 

Associated Types

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

Generic (Code High) # 

Associated Types

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

Methods

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

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

Generic (BootstrapMethod High) # 
Generic (BootstrapMethods High) # 
Generic (MethodAttributes High) # 
Generic (Method High) # 

Associated Types

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

Methods

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

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

Generic (FieldAttributes High) # 
Generic (Field High) # 

Associated Types

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

Methods

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

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

Generic (ClassAttributes High) # 
Generic (ClassFile High) # 

Associated Types

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

NFData (InvokeDynamic High) # 

Methods

rnf :: InvokeDynamic High -> () #

NFData (MethodHandleInterface High) # 
NFData (MethodHandleMethod High) # 

Methods

rnf :: MethodHandleMethod High -> () #

NFData (MethodHandleField High) # 

Methods

rnf :: MethodHandleField High -> () #

NFData (MethodHandle High) # 

Methods

rnf :: MethodHandle High -> () #

NFData (AbsVariableMethodId High) # 

Methods

rnf :: AbsVariableMethodId High -> () #

NFData (AbsInterfaceMethodId High) # 

Methods

rnf :: AbsInterfaceMethodId High -> () #

NFData (Constant High) # 

Methods

rnf :: Constant High -> () #

NFData (ConstantPool High) # 

Methods

rnf :: ConstantPool High -> () #

NFData (ByteCodeOpr High) # 

Methods

rnf :: ByteCodeOpr High -> () #

NFData (SwitchTable High) # 

Methods

rnf :: SwitchTable High -> () #

NFData (CConstant High) # 

Methods

rnf :: CConstant High -> () #

NFData (Invocation High) # 

Methods

rnf :: Invocation High -> () #

NFData (ExactArrayType High) # 

Methods

rnf :: ExactArrayType High -> () #

NFData (ByteCodeInst High) # 

Methods

rnf :: ByteCodeInst High -> () #

NFData (ByteCode High) # 

Methods

rnf :: ByteCode High -> () #

NFData (Attribute High) # 

Methods

rnf :: Attribute High -> () #

NFData (VerificationTypeInfo High) # 

Methods

rnf :: VerificationTypeInfo High -> () #

NFData (StackMapFrameType High) # 

Methods

rnf :: StackMapFrameType High -> () #

NFData (StackMapFrame High) # 

Methods

rnf :: StackMapFrame High -> () #

NFData (StackMapTable High) # 

Methods

rnf :: StackMapTable High -> () #

NFData (Signature High) # 

Methods

rnf :: Signature High -> () #

NFData (Exceptions High) # 

Methods

rnf :: Exceptions High -> () #

NFData (ConstantValue High) # 

Methods

rnf :: ConstantValue High -> () #

NFData (CodeAttributes High) # 

Methods

rnf :: CodeAttributes High -> () #

NFData (ExceptionTable High) # 

Methods

rnf :: ExceptionTable High -> () #

NFData (Code High) # 

Methods

rnf :: Code High -> () #

NFData (BootstrapMethod High) # 

Methods

rnf :: BootstrapMethod High -> () #

NFData (BootstrapMethods High) # 

Methods

rnf :: BootstrapMethods High -> () #

NFData (MethodAttributes High) # 

Methods

rnf :: MethodAttributes High -> () #

NFData (Method High) # 

Methods

rnf :: Method High -> () #

NFData (FieldAttributes High) # 

Methods

rnf :: FieldAttributes High -> () #

NFData (Field High) # 

Methods

rnf :: Field High -> () #

NFData (ClassAttributes High) # 

Methods

rnf :: ClassAttributes High -> () #

NFData (ClassFile High) # 

Methods

rnf :: ClassFile High -> () #

Referenceable (InvokeDynamic High) Source # 

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 # 

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 # 
Referenceable (AbsInterfaceMethodId High) Source # 
Referenceable (Constant High) Source # 

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) # 
Eq (InClass MethodId High) # 
Show (InClass FieldId High) # 
Show (InClass MethodId High) # 
Generic (InClass FieldId High) # 

Associated Types

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

Generic (InClass MethodId High) # 

Associated Types

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

NFData (InClass FieldId High) # 

Methods

rnf :: InClass FieldId High -> () #

NFData (InClass MethodId High) # 

Methods

rnf :: InClass MethodId High -> () #

Referenceable (InClass FieldId High) Source # 

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 # 

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 #

MonadReader (String, ConstantPool High) Evolve # 
type Choice a b High Source # 
type Choice a b High = b
type Rep (InvokeDynamic High) # 
type Rep (InvokeDynamic High) = D1 * (MetaData "InvokeDynamic" "Language.JVM.Constant" "jvm-binary-0.1.0-JJ8Rr7ERir79pQaBJvdiXV" False) (C1 * (MetaCons "InvokeDynamic" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "invokeDynamicAttrIndex") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Word16)) (S1 * (MetaSel (Just Symbol "invokeDynamicMethod") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Ref MethodId High)))))
type Rep (MethodHandleInterface High) # 
type Rep (MethodHandleInterface High) = D1 * (MetaData "MethodHandleInterface" "Language.JVM.Constant" "jvm-binary-0.1.0-JJ8Rr7ERir79pQaBJvdiXV" False) (C1 * (MetaCons "MethodHandleInterface" PrefixI True) (S1 * (MetaSel (Just Symbol "methodHandleInterfaceRef") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (DeepRef AbsInterfaceMethodId High))))
type Rep (MethodHandleMethod High) # 
type Rep (MethodHandleField High) # 
type Rep (MethodHandleField High) = D1 * (MetaData "MethodHandleField" "Language.JVM.Constant" "jvm-binary-0.1.0-JJ8Rr7ERir79pQaBJvdiXV" False) (C1 * (MetaCons "MethodHandleField" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "methodHandleFieldKind") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * MethodHandleFieldKind)) (S1 * (MetaSel (Just Symbol "methodHandleFieldRef") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (DeepRef AbsFieldId High)))))
type Rep (MethodHandle High) # 
type Rep (AbsVariableMethodId High) # 
type Rep (AbsVariableMethodId High) = D1 * (MetaData "AbsVariableMethodId" "Language.JVM.Constant" "jvm-binary-0.1.0-JJ8Rr7ERir79pQaBJvdiXV" False) ((:+:) * (C1 * (MetaCons "VInterfaceMethodId" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (AbsInterfaceMethodId High)))) (C1 * (MetaCons "VMethodId" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (AbsMethodId High)))))
type Rep (AbsInterfaceMethodId High) # 
type Rep (AbsInterfaceMethodId High) = D1 * (MetaData "AbsInterfaceMethodId" "Language.JVM.Constant" "jvm-binary-0.1.0-JJ8Rr7ERir79pQaBJvdiXV" True) (C1 * (MetaCons "AbsInterfaceMethodId" PrefixI True) (S1 * (MetaSel (Just Symbol "interfaceMethodId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (InClass MethodId High))))
type Rep (Constant High) # 
type Rep (Constant High) = D1 * (MetaData "Constant" "Language.JVM.Constant" "jvm-binary-0.1.0-JJ8Rr7ERir79pQaBJvdiXV" False) ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "CString" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * SizedByteString16))) ((:+:) * (C1 * (MetaCons "CInteger" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Int32))) (C1 * (MetaCons "CFloat" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Float))))) ((:+:) * ((:+:) * (C1 * (MetaCons "CLong" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Int64))) (C1 * (MetaCons "CDouble" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Double)))) ((:+:) * (C1 * (MetaCons "CClassRef" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Ref Text High)))) (C1 * (MetaCons "CStringRef" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Ref ByteString High))))))) ((:+:) * ((:+:) * (C1 * (MetaCons "CFieldRef" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (InClass FieldId High)))) ((:+:) * (C1 * (MetaCons "CMethodRef" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (InClass MethodId High)))) (C1 * (MetaCons "CInterfaceMethodRef" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (InClass MethodId High)))))) ((:+:) * ((:+:) * (C1 * (MetaCons "CNameAndType" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Ref Text High))) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Ref Text High))))) (C1 * (MetaCons "CMethodHandle" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (MethodHandle High))))) ((:+:) * (C1 * (MetaCons "CMethodType" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Ref MethodDescriptor High)))) (C1 * (MetaCons "CInvokeDynamic" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (InvokeDynamic High))))))))
type Rep (ConstantPool High) # 
type Rep (ConstantPool High) = D1 * (MetaData "ConstantPool" "Language.JVM.ConstantPool" "jvm-binary-0.1.0-JJ8Rr7ERir79pQaBJvdiXV" True) (C1 * (MetaCons "ConstantPool" PrefixI True) (S1 * (MetaSel (Just Symbol "unConstantPool") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (IntMap (Constant High)))))
type Rep (ByteCodeOpr High) # 
type Rep (SwitchTable High) # 
type Rep (CConstant High) # 
type Rep (CConstant High) = D1 * (MetaData "CConstant" "Language.JVM.ByteCode" "jvm-binary-0.1.0-JJ8Rr7ERir79pQaBJvdiXV" False) ((:+:) * ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "CNull" PrefixI False) (U1 *)) (C1 * (MetaCons "CIntM1" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "CInt0" PrefixI False) (U1 *)) (C1 * (MetaCons "CInt1" PrefixI False) (U1 *)))) ((:+:) * ((:+:) * (C1 * (MetaCons "CInt2" PrefixI False) (U1 *)) (C1 * (MetaCons "CInt3" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "CInt4" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "CInt5" PrefixI False) (U1 *)) (C1 * (MetaCons "CLong0" PrefixI False) (U1 *)))))) ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "CLong1" PrefixI False) (U1 *)) (C1 * (MetaCons "CFloat0" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "CFloat1" PrefixI False) (U1 *)) (C1 * (MetaCons "CFloat2" PrefixI False) (U1 *)))) ((:+:) * ((:+:) * (C1 * (MetaCons "CDouble0" PrefixI False) (U1 *)) (C1 * (MetaCons "CDouble1" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "CByte" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Int8))) ((:+:) * (C1 * (MetaCons "CShort" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Int16))) (C1 * (MetaCons "CRef" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe WordSize))) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Ref JValue High))))))))))
type Rep (Invocation High) # 
type Rep (ExactArrayType High) # 
type Rep (ExactArrayType High) = D1 * (MetaData "ExactArrayType" "Language.JVM.ByteCode" "jvm-binary-0.1.0-JJ8Rr7ERir79pQaBJvdiXV" False) ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "EABoolean" PrefixI False) (U1 *)) (C1 * (MetaCons "EAByte" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "EAChar" PrefixI False) (U1 *)) (C1 * (MetaCons "EAShort" PrefixI False) (U1 *)))) ((:+:) * ((:+:) * (C1 * (MetaCons "EAInt" PrefixI False) (U1 *)) (C1 * (MetaCons "EALong" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "EAFloat" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "EADouble" PrefixI False) (U1 *)) (C1 * (MetaCons "EARef" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Ref ClassName High))))))))
type Rep (ByteCodeInst High) # 
type Rep (ByteCodeInst High) = D1 * (MetaData "ByteCodeInst" "Language.JVM.ByteCode" "jvm-binary-0.1.0-JJ8Rr7ERir79pQaBJvdiXV" False) (C1 * (MetaCons "ByteCodeInst" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "offset") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * ByteCodeOffset)) (S1 * (MetaSel (Just Symbol "opcode") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (ByteCodeOpr High)))))
type Rep (ByteCode High) # 
type Rep (ByteCode High) = D1 * (MetaData "ByteCode" "Language.JVM.ByteCode" "jvm-binary-0.1.0-JJ8Rr7ERir79pQaBJvdiXV" True) (C1 * (MetaCons "ByteCode" PrefixI True) (S1 * (MetaSel (Just Symbol "unByteCode") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Choice (Word32, Vector (ByteCodeInst Low)) (Vector (ByteCodeOpr High)) High))))
type Rep (Attribute High) # 
type Rep (Attribute High) = D1 * (MetaData "Attribute" "Language.JVM.Attribute.Base" "jvm-binary-0.1.0-JJ8Rr7ERir79pQaBJvdiXV" False) (C1 * (MetaCons "Attribute" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "aName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Ref Text High))) (S1 * (MetaSel (Just Symbol "aInfo'") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * SizedByteString32))))
type Rep (VerificationTypeInfo High) # 
type Rep (VerificationTypeInfo High) = D1 * (MetaData "VerificationTypeInfo" "Language.JVM.Attribute.StackMapTable" "jvm-binary-0.1.0-JJ8Rr7ERir79pQaBJvdiXV" False) ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "VTTop" PrefixI False) (U1 *)) (C1 * (MetaCons "VTInteger" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "VTFloat" PrefixI False) (U1 *)) (C1 * (MetaCons "VTLong" PrefixI False) (U1 *)))) ((:+:) * ((:+:) * (C1 * (MetaCons "VTDouble" PrefixI False) (U1 *)) (C1 * (MetaCons "VTNull" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "VTUninitializedThis" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "VTObject" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Ref ClassName High)))) (C1 * (MetaCons "VTUninitialized" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Word16)))))))
type Rep (StackMapFrameType High) # 
type Rep (StackMapFrame High) # 
type Rep (StackMapFrame High) = D1 * (MetaData "StackMapFrame" "Language.JVM.Attribute.StackMapTable" "jvm-binary-0.1.0-JJ8Rr7ERir79pQaBJvdiXV" False) (C1 * (MetaCons "StackMapFrame" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "deltaOffset") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (DeltaOffset High))) (S1 * (MetaSel (Just Symbol "frameType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (StackMapFrameType High)))))
type Rep (StackMapTable High) # 
type Rep (StackMapTable High) = D1 * (MetaData "StackMapTable" "Language.JVM.Attribute.StackMapTable" "jvm-binary-0.1.0-JJ8Rr7ERir79pQaBJvdiXV" True) (C1 * (MetaCons "StackMapTable" PrefixI True) (S1 * (MetaSel (Just Symbol "stackMapTable") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Choice (SizedList16 (StackMapFrame Low)) [StackMapFrame High] High))))
type Rep (Signature High) # 
type Rep (Signature High) = D1 * (MetaData "Signature" "Language.JVM.Attribute.Signature" "jvm-binary-0.1.0-JJ8Rr7ERir79pQaBJvdiXV" False) (C1 * (MetaCons "Signature" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Ref Text High))))
type Rep (Exceptions High) # 
type Rep (Exceptions High) = D1 * (MetaData "Exceptions" "Language.JVM.Attribute.Exceptions" "jvm-binary-0.1.0-JJ8Rr7ERir79pQaBJvdiXV" True) (C1 * (MetaCons "Exceptions" PrefixI True) (S1 * (MetaSel (Just Symbol "exceptions") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (SizedList16 (Ref ClassName High)))))
type Rep (ConstantValue High) # 
type Rep (ConstantValue High) = D1 * (MetaData "ConstantValue" "Language.JVM.Attribute.ConstantValue" "jvm-binary-0.1.0-JJ8Rr7ERir79pQaBJvdiXV" False) (C1 * (MetaCons "ConstantValue" PrefixI True) (S1 * (MetaSel (Just Symbol "constantValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Ref JValue High))))
type Rep (CodeAttributes High) # 
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 (ExceptionTable High) # 
type Rep (Code High) # 
type Rep (BootstrapMethod High) # 
type Rep (BootstrapMethod High) = D1 * (MetaData "BootstrapMethod" "Language.JVM.Attribute.BootstrapMethods" "jvm-binary-0.1.0-JJ8Rr7ERir79pQaBJvdiXV" False) (C1 * (MetaCons "BootstrapMethod" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "method") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (DeepRef MethodHandle High))) (S1 * (MetaSel (Just Symbol "arguments") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (SizedList16 (Ref JValue High))))))
type Rep (BootstrapMethods High) # 
type Rep (BootstrapMethods High) = D1 * (MetaData "BootstrapMethods" "Language.JVM.Attribute.BootstrapMethods" "jvm-binary-0.1.0-JJ8Rr7ERir79pQaBJvdiXV" True) (C1 * (MetaCons "BootstrapMethods" PrefixI True) (S1 * (MetaSel (Just Symbol "methods'") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (SizedList16 (BootstrapMethod High)))))
type Rep (MethodAttributes High) # 
type Rep (Method High) # 
type Rep (FieldAttributes High) # 
type Rep (FieldAttributes High) = D1 * (MetaData "FieldAttributes" "Language.JVM.Field" "jvm-binary-0.1.0-JJ8Rr7ERir79pQaBJvdiXV" False) (C1 * (MetaCons "FieldAttributes" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "faConstantValues") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [ConstantValue High])) ((:*:) * (S1 * (MetaSel (Just Symbol "faSignatures") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [Signature High])) (S1 * (MetaSel (Just Symbol "faOthers") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [Attribute High])))))
type Rep (Field High) # 
type Rep (ClassAttributes High) # 
type Rep (ClassAttributes High) = D1 * (MetaData "ClassAttributes" "Language.JVM.ClassFile" "jvm-binary-0.1.0-JJ8Rr7ERir79pQaBJvdiXV" False) (C1 * (MetaCons "ClassAttributes" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "caBootstrapMethods") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [BootstrapMethods High])) ((:*:) * (S1 * (MetaSel (Just Symbol "caSignature") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [Signature High])) (S1 * (MetaSel (Just Symbol "caOthers") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [Attribute High])))))
type Rep (ClassFile High) # 
type Rep (ClassFile High) = D1 * (MetaData "ClassFile" "Language.JVM.ClassFile" "jvm-binary-0.1.0-JJ8Rr7ERir79pQaBJvdiXV" False) (C1 * (MetaCons "ClassFile" PrefixI True) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "cMagicNumber") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Word32)) (S1 * (MetaSel (Just Symbol "cMinorVersion") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Word16))) ((:*:) * (S1 * (MetaSel (Just Symbol "cMajorVersion") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Word16)) ((:*:) * (S1 * (MetaSel (Just Symbol "cConstantPool") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Choice (ConstantPool High) () High))) (S1 * (MetaSel (Just Symbol "cAccessFlags'") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (BitSet16 CAccessFlag)))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "cThisClass") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Ref ClassName High))) ((:*:) * (S1 * (MetaSel (Just Symbol "cSuperClass") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Ref ClassName High))) (S1 * (MetaSel (Just Symbol "cInterfaces") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (SizedList16 (Ref ClassName High)))))) ((:*:) * (S1 * (MetaSel (Just Symbol "cFields'") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (SizedList16 (Field High)))) ((:*:) * (S1 * (MetaSel (Just Symbol "cMethods'") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (SizedList16 (Method High)))) (S1 * (MetaSel (Just Symbol "cAttributes") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Attributes ClassAttributes High))))))))
type Rep (InClass FieldId High) # 
type Rep (InClass FieldId High) = D1 * (MetaData "InClass" "Language.JVM.Constant" "jvm-binary-0.1.0-JJ8Rr7ERir79pQaBJvdiXV" False) (C1 * (MetaCons "InClass" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "inClassName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Ref ClassName High))) (S1 * (MetaSel (Just Symbol "inClassId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Ref FieldId High)))))
type Rep (InClass MethodId High) # 
type Rep (InClass MethodId High) = D1 * (MetaData "InClass" "Language.JVM.Constant" "jvm-binary-0.1.0-JJ8Rr7ERir79pQaBJvdiXV" False) (C1 * (MetaCons "InClass" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "inClassName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Ref ClassName High))) (S1 * (MetaSel (Just Symbol "inClassId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Ref MethodId High)))))

data Low Source #

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

Instances

Eq (InvokeDynamic Low) # 
Eq (MethodHandleInterface Low) # 
Eq (MethodHandleMethod Low) # 
Eq (MethodHandleField Low) # 
Eq (MethodHandle Low) # 
Eq (AbsVariableMethodId Low) # 
Eq (AbsInterfaceMethodId Low) # 
Eq (Constant Low) # 
Eq (ConstantPool Low) # 
Eq (ByteCodeOpr Low) # 
Eq (SwitchTable Low) # 
Eq (CConstant Low) # 
Eq (Invocation Low) # 
Eq (ExactArrayType Low) # 
Eq (ByteCodeInst Low) # 
Eq (ByteCode Low) # 
Eq (Attribute Low) # 
Eq (VerificationTypeInfo Low) # 
Eq (StackMapFrameType Low) # 
Eq (StackMapFrame Low) # 
Eq (StackMapTable Low) # 
Eq (Signature Low) # 
Eq (Exceptions Low) # 
Eq (ConstantValue Low) # 
Eq (CodeAttributes Low) # 
Eq (ExceptionTable Low) # 
Eq (Code Low) # 

Methods

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

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

Eq (BootstrapMethod Low) # 
Eq (BootstrapMethods Low) # 
Eq (MethodAttributes Low) # 
Eq (Method Low) # 

Methods

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

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

Eq (FieldAttributes Low) # 
Eq (Field Low) # 

Methods

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

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

Eq (ClassAttributes Low) # 
Eq (ClassFile Low) # 
Ord (InvokeDynamic Low) # 
Ord (MethodHandleInterface Low) # 
Ord (MethodHandleMethod Low) # 
Ord (MethodHandleField Low) # 
Ord (MethodHandle Low) # 
Ord (AbsVariableMethodId Low) # 
Ord (AbsInterfaceMethodId Low) # 
Ord (Constant Low) # 
Ord (ConstantPool Low) # 
Ord (ByteCodeOpr Low) # 
Ord (SwitchTable Low) # 
Ord (CConstant Low) # 
Ord (Invocation Low) # 
Ord (ExactArrayType Low) # 
Ord (ByteCodeInst Low) # 
Ord (ByteCode Low) # 
Ord (Attribute Low) # 
Ord (VerificationTypeInfo Low) # 
Ord (StackMapFrameType Low) # 
Ord (StackMapFrame Low) # 
Ord (StackMapTable Low) # 
Ord (Signature Low) # 
Ord (Exceptions Low) # 
Ord (ConstantValue Low) # 
Ord (CodeAttributes Low) # 
Ord (ExceptionTable Low) # 
Ord (Code Low) # 

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) # 
Ord (BootstrapMethods Low) # 
Ord (MethodAttributes Low) # 
Ord (Method Low) # 
Ord (FieldAttributes Low) # 
Ord (Field Low) # 
Ord (ClassAttributes Low) # 
Ord (ClassFile Low) # 
Show (InvokeDynamic Low) # 
Show (MethodHandleInterface Low) # 
Show (MethodHandleMethod Low) # 
Show (MethodHandleField Low) # 
Show (MethodHandle Low) # 
Show (AbsVariableMethodId Low) # 
Show (AbsInterfaceMethodId Low) # 
Show (Constant Low) # 
Show (ConstantPool Low) # 
Show (ByteCodeOpr Low) # 
Show (SwitchTable Low) # 
Show (CConstant Low) # 
Show (Invocation Low) # 
Show (ExactArrayType Low) # 
Show (ByteCodeInst Low) # 
Show (ByteCode Low) # 
Show (Attribute Low) # 
Show (VerificationTypeInfo Low) # 
Show (StackMapFrameType Low) # 
Show (StackMapFrame Low) # 
Show (StackMapTable Low) # 
Show (Signature Low) # 
Show (Exceptions Low) # 
Show (ConstantValue Low) # 
Show (CodeAttributes Low) # 
Show (ExceptionTable Low) # 
Show (Code Low) # 

Methods

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

show :: Code Low -> String #

showList :: [Code Low] -> ShowS #

Show (BootstrapMethod Low) # 
Show (BootstrapMethods Low) # 
Show (MethodAttributes Low) # 
Show (Method Low) # 
Show (FieldAttributes Low) # 
Show (Field Low) # 
Show (ClassAttributes Low) # 
Show (ClassFile Low) # 
Generic (InvokeDynamic Low) # 

Associated Types

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

Generic (MethodHandleInterface Low) # 
Generic (MethodHandleMethod Low) # 
Generic (MethodHandleField Low) # 
Generic (MethodHandle Low) # 

Associated Types

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

Generic (AbsVariableMethodId Low) # 
Generic (AbsInterfaceMethodId Low) # 
Generic (Constant Low) # 

Associated Types

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

Methods

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

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

Generic (ConstantPool Low) # 

Associated Types

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

Generic (ByteCodeOpr Low) # 

Associated Types

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

Generic (SwitchTable Low) # 

Associated Types

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

Generic (CConstant Low) # 

Associated Types

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

Generic (Invocation Low) # 

Associated Types

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

Generic (ExactArrayType Low) # 

Associated Types

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

Generic (ByteCodeInst Low) # 

Associated Types

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

Generic (ByteCode Low) # 

Associated Types

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

Methods

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

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

Generic (Attribute Low) # 

Associated Types

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

Generic (VerificationTypeInfo Low) # 
Generic (StackMapFrameType Low) # 
Generic (StackMapFrame Low) # 

Associated Types

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

Generic (StackMapTable Low) # 

Associated Types

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

Generic (Signature Low) # 

Associated Types

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

Generic (Exceptions Low) # 

Associated Types

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

Generic (ConstantValue Low) # 

Associated Types

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

Generic (CodeAttributes Low) # 

Associated Types

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

Generic (ExceptionTable Low) # 

Associated Types

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

Generic (Code Low) # 

Associated Types

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

Methods

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

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

Generic (BootstrapMethod Low) # 

Associated Types

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

Generic (BootstrapMethods Low) # 
Generic (MethodAttributes Low) # 
Generic (Method Low) # 

Associated Types

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

Methods

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

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

Generic (FieldAttributes Low) # 

Associated Types

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

Generic (Field Low) # 

Associated Types

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

Methods

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

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

Generic (ClassAttributes Low) # 

Associated Types

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

Generic (ClassFile Low) # 

Associated Types

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

Binary (InvokeDynamic Low) # 
Binary (MethodHandle Low) # 
Binary (AbsVariableMethodId Low) # 
Binary (AbsInterfaceMethodId Low) # 
Binary (Constant Low) # 
Binary (ConstantPool Low) # 
Binary (ByteCodeOpr Low) # 
Binary (ByteCodeInst Low) # 
Binary (ByteCode Low) # 
Binary (Attribute Low) # 
Binary (VerificationTypeInfo Low) # 
Binary (StackMapFrame Low) # 
Binary (StackMapTable Low) # 
Binary (Signature Low) # 
Binary (LineNumberTable Low) # 
Binary (Exceptions Low) # 
Binary (ConstantValue Low) # 
Binary (ExceptionTable Low) # 
Binary (Code Low) # 

Methods

put :: Code Low -> Put #

get :: Get (Code Low) #

putList :: [Code Low] -> Put #

Binary (BootstrapMethod Low) # 
Binary (BootstrapMethods Low) # 
Binary (Method Low) # 

Methods

put :: Method Low -> Put #

get :: Get (Method Low) #

putList :: [Method Low] -> Put #

Binary (Field Low) # 

Methods

put :: Field Low -> Put #

get :: Get (Field Low) #

putList :: [Field Low] -> Put #

Binary (ClassFile Low) # 
NFData (InvokeDynamic Low) # 

Methods

rnf :: InvokeDynamic Low -> () #

NFData (MethodHandleInterface Low) # 

Methods

rnf :: MethodHandleInterface Low -> () #

NFData (MethodHandleMethod Low) # 

Methods

rnf :: MethodHandleMethod Low -> () #

NFData (MethodHandleField Low) # 

Methods

rnf :: MethodHandleField Low -> () #

NFData (MethodHandle Low) # 

Methods

rnf :: MethodHandle Low -> () #

NFData (AbsVariableMethodId Low) # 

Methods

rnf :: AbsVariableMethodId Low -> () #

NFData (AbsInterfaceMethodId Low) # 

Methods

rnf :: AbsInterfaceMethodId Low -> () #

NFData (Constant Low) # 

Methods

rnf :: Constant Low -> () #

NFData (ConstantPool Low) # 

Methods

rnf :: ConstantPool Low -> () #

NFData (ByteCodeOpr Low) # 

Methods

rnf :: ByteCodeOpr Low -> () #

NFData (SwitchTable Low) # 

Methods

rnf :: SwitchTable Low -> () #

NFData (CConstant Low) # 

Methods

rnf :: CConstant Low -> () #

NFData (Invocation Low) # 

Methods

rnf :: Invocation Low -> () #

NFData (ExactArrayType Low) # 

Methods

rnf :: ExactArrayType Low -> () #

NFData (ByteCodeInst Low) # 

Methods

rnf :: ByteCodeInst Low -> () #

NFData (ByteCode Low) # 

Methods

rnf :: ByteCode Low -> () #

NFData (Attribute Low) # 

Methods

rnf :: Attribute Low -> () #

NFData (VerificationTypeInfo Low) # 

Methods

rnf :: VerificationTypeInfo Low -> () #

NFData (StackMapFrameType Low) # 

Methods

rnf :: StackMapFrameType Low -> () #

NFData (StackMapFrame Low) # 

Methods

rnf :: StackMapFrame Low -> () #

NFData (StackMapTable Low) # 

Methods

rnf :: StackMapTable Low -> () #

NFData (Signature Low) # 

Methods

rnf :: Signature Low -> () #

NFData (Exceptions Low) # 

Methods

rnf :: Exceptions Low -> () #

NFData (ConstantValue Low) # 

Methods

rnf :: ConstantValue Low -> () #

NFData (CodeAttributes Low) # 

Methods

rnf :: CodeAttributes Low -> () #

NFData (ExceptionTable Low) # 

Methods

rnf :: ExceptionTable Low -> () #

NFData (Code Low) # 

Methods

rnf :: Code Low -> () #

NFData (BootstrapMethod Low) # 

Methods

rnf :: BootstrapMethod Low -> () #

NFData (BootstrapMethods Low) # 

Methods

rnf :: BootstrapMethods Low -> () #

NFData (MethodAttributes Low) # 

Methods

rnf :: MethodAttributes Low -> () #

NFData (Method Low) # 

Methods

rnf :: Method Low -> () #

NFData (FieldAttributes Low) # 

Methods

rnf :: FieldAttributes Low -> () #

NFData (Field Low) # 

Methods

rnf :: Field Low -> () #

NFData (ClassAttributes Low) # 

Methods

rnf :: ClassAttributes Low -> () #

NFData (ClassFile Low) # 

Methods

rnf :: ClassFile Low -> () #

IsAttribute (StackMapTable Low) Source #

StackMapTable is an Attribute.

IsAttribute (Signature Low) Source # 
IsAttribute (LineNumberTable Low) Source #

Signature is an Attribute.

IsAttribute (Exceptions Low) Source #

Exceptions is an Attribute.

IsAttribute (ConstantValue Low) Source #

ConstantValue is an Attribute.

IsAttribute (Code Low) Source #

Code is an Attribute.

IsAttribute (BootstrapMethods Low) Source #

BootstrapMethods is an Attribute.

Eq (InClass FieldId Low) # 
Eq (InClass MethodId Low) # 
Ord (InClass FieldId Low) # 
Ord (InClass MethodId Low) # 
Show (InClass FieldId Low) # 
Show (InClass MethodId Low) # 
Generic (InClass FieldId Low) # 

Associated Types

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

Generic (InClass MethodId Low) # 

Associated Types

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

Binary (InClass FieldId Low) # 
Binary (InClass MethodId Low) # 
NFData (InClass FieldId Low) # 

Methods

rnf :: InClass FieldId Low -> () #

NFData (InClass MethodId Low) # 

Methods

rnf :: InClass MethodId Low -> () #

type Choice a b Low Source # 
type Choice a b Low = a
type Rep (InvokeDynamic Low) # 
type Rep (InvokeDynamic Low) = D1 * (MetaData "InvokeDynamic" "Language.JVM.Constant" "jvm-binary-0.1.0-JJ8Rr7ERir79pQaBJvdiXV" False) (C1 * (MetaCons "InvokeDynamic" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "invokeDynamicAttrIndex") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Word16)) (S1 * (MetaSel (Just Symbol "invokeDynamicMethod") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Ref MethodId Low)))))
type Rep (MethodHandleInterface Low) # 
type Rep (MethodHandleInterface Low) = D1 * (MetaData "MethodHandleInterface" "Language.JVM.Constant" "jvm-binary-0.1.0-JJ8Rr7ERir79pQaBJvdiXV" False) (C1 * (MetaCons "MethodHandleInterface" PrefixI True) (S1 * (MetaSel (Just Symbol "methodHandleInterfaceRef") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (DeepRef AbsInterfaceMethodId Low))))
type Rep (MethodHandleMethod Low) # 
type Rep (MethodHandleField Low) # 
type Rep (MethodHandleField Low) = D1 * (MetaData "MethodHandleField" "Language.JVM.Constant" "jvm-binary-0.1.0-JJ8Rr7ERir79pQaBJvdiXV" False) (C1 * (MetaCons "MethodHandleField" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "methodHandleFieldKind") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * MethodHandleFieldKind)) (S1 * (MetaSel (Just Symbol "methodHandleFieldRef") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (DeepRef AbsFieldId Low)))))
type Rep (MethodHandle Low) # 
type Rep (AbsVariableMethodId Low) # 
type Rep (AbsVariableMethodId Low) = D1 * (MetaData "AbsVariableMethodId" "Language.JVM.Constant" "jvm-binary-0.1.0-JJ8Rr7ERir79pQaBJvdiXV" False) ((:+:) * (C1 * (MetaCons "VInterfaceMethodId" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (AbsInterfaceMethodId Low)))) (C1 * (MetaCons "VMethodId" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (AbsMethodId Low)))))
type Rep (AbsInterfaceMethodId Low) # 
type Rep (AbsInterfaceMethodId Low) = D1 * (MetaData "AbsInterfaceMethodId" "Language.JVM.Constant" "jvm-binary-0.1.0-JJ8Rr7ERir79pQaBJvdiXV" True) (C1 * (MetaCons "AbsInterfaceMethodId" PrefixI True) (S1 * (MetaSel (Just Symbol "interfaceMethodId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (InClass MethodId Low))))
type Rep (Constant Low) # 
type Rep (Constant Low) = D1 * (MetaData "Constant" "Language.JVM.Constant" "jvm-binary-0.1.0-JJ8Rr7ERir79pQaBJvdiXV" False) ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "CString" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * SizedByteString16))) ((:+:) * (C1 * (MetaCons "CInteger" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Int32))) (C1 * (MetaCons "CFloat" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Float))))) ((:+:) * ((:+:) * (C1 * (MetaCons "CLong" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Int64))) (C1 * (MetaCons "CDouble" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Double)))) ((:+:) * (C1 * (MetaCons "CClassRef" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Ref Text Low)))) (C1 * (MetaCons "CStringRef" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Ref ByteString Low))))))) ((:+:) * ((:+:) * (C1 * (MetaCons "CFieldRef" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (InClass FieldId Low)))) ((:+:) * (C1 * (MetaCons "CMethodRef" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (InClass MethodId Low)))) (C1 * (MetaCons "CInterfaceMethodRef" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (InClass MethodId Low)))))) ((:+:) * ((:+:) * (C1 * (MetaCons "CNameAndType" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Ref Text Low))) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Ref Text Low))))) (C1 * (MetaCons "CMethodHandle" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (MethodHandle Low))))) ((:+:) * (C1 * (MetaCons "CMethodType" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Ref MethodDescriptor Low)))) (C1 * (MetaCons "CInvokeDynamic" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (InvokeDynamic Low))))))))
type Rep (ConstantPool Low) # 
type Rep (ConstantPool Low) = D1 * (MetaData "ConstantPool" "Language.JVM.ConstantPool" "jvm-binary-0.1.0-JJ8Rr7ERir79pQaBJvdiXV" True) (C1 * (MetaCons "ConstantPool" PrefixI True) (S1 * (MetaSel (Just Symbol "unConstantPool") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (IntMap (Constant Low)))))
type Rep (ByteCodeOpr Low) # 
type Rep (SwitchTable Low) # 
type Rep (CConstant Low) # 
type Rep (CConstant Low) = D1 * (MetaData "CConstant" "Language.JVM.ByteCode" "jvm-binary-0.1.0-JJ8Rr7ERir79pQaBJvdiXV" False) ((:+:) * ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "CNull" PrefixI False) (U1 *)) (C1 * (MetaCons "CIntM1" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "CInt0" PrefixI False) (U1 *)) (C1 * (MetaCons "CInt1" PrefixI False) (U1 *)))) ((:+:) * ((:+:) * (C1 * (MetaCons "CInt2" PrefixI False) (U1 *)) (C1 * (MetaCons "CInt3" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "CInt4" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "CInt5" PrefixI False) (U1 *)) (C1 * (MetaCons "CLong0" PrefixI False) (U1 *)))))) ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "CLong1" PrefixI False) (U1 *)) (C1 * (MetaCons "CFloat0" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "CFloat1" PrefixI False) (U1 *)) (C1 * (MetaCons "CFloat2" PrefixI False) (U1 *)))) ((:+:) * ((:+:) * (C1 * (MetaCons "CDouble0" PrefixI False) (U1 *)) (C1 * (MetaCons "CDouble1" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "CByte" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Int8))) ((:+:) * (C1 * (MetaCons "CShort" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Int16))) (C1 * (MetaCons "CRef" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe WordSize))) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Ref JValue Low))))))))))
type Rep (Invocation Low) # 
type Rep (ExactArrayType Low) # 
type Rep (ExactArrayType Low) = D1 * (MetaData "ExactArrayType" "Language.JVM.ByteCode" "jvm-binary-0.1.0-JJ8Rr7ERir79pQaBJvdiXV" False) ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "EABoolean" PrefixI False) (U1 *)) (C1 * (MetaCons "EAByte" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "EAChar" PrefixI False) (U1 *)) (C1 * (MetaCons "EAShort" PrefixI False) (U1 *)))) ((:+:) * ((:+:) * (C1 * (MetaCons "EAInt" PrefixI False) (U1 *)) (C1 * (MetaCons "EALong" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "EAFloat" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "EADouble" PrefixI False) (U1 *)) (C1 * (MetaCons "EARef" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Ref ClassName Low))))))))
type Rep (ByteCodeInst Low) # 
type Rep (ByteCodeInst Low) = D1 * (MetaData "ByteCodeInst" "Language.JVM.ByteCode" "jvm-binary-0.1.0-JJ8Rr7ERir79pQaBJvdiXV" False) (C1 * (MetaCons "ByteCodeInst" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "offset") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * ByteCodeOffset)) (S1 * (MetaSel (Just Symbol "opcode") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (ByteCodeOpr Low)))))
type Rep (ByteCode Low) # 
type Rep (ByteCode Low) = D1 * (MetaData "ByteCode" "Language.JVM.ByteCode" "jvm-binary-0.1.0-JJ8Rr7ERir79pQaBJvdiXV" True) (C1 * (MetaCons "ByteCode" PrefixI True) (S1 * (MetaSel (Just Symbol "unByteCode") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Choice (Word32, Vector (ByteCodeInst Low)) (Vector (ByteCodeOpr High)) Low))))
type Rep (Attribute Low) # 
type Rep (Attribute Low) = D1 * (MetaData "Attribute" "Language.JVM.Attribute.Base" "jvm-binary-0.1.0-JJ8Rr7ERir79pQaBJvdiXV" False) (C1 * (MetaCons "Attribute" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "aName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Ref Text Low))) (S1 * (MetaSel (Just Symbol "aInfo'") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * SizedByteString32))))
type Rep (VerificationTypeInfo Low) # 
type Rep (VerificationTypeInfo Low) = D1 * (MetaData "VerificationTypeInfo" "Language.JVM.Attribute.StackMapTable" "jvm-binary-0.1.0-JJ8Rr7ERir79pQaBJvdiXV" False) ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "VTTop" PrefixI False) (U1 *)) (C1 * (MetaCons "VTInteger" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "VTFloat" PrefixI False) (U1 *)) (C1 * (MetaCons "VTLong" PrefixI False) (U1 *)))) ((:+:) * ((:+:) * (C1 * (MetaCons "VTDouble" PrefixI False) (U1 *)) (C1 * (MetaCons "VTNull" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "VTUninitializedThis" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "VTObject" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Ref ClassName Low)))) (C1 * (MetaCons "VTUninitialized" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Word16)))))))
type Rep (StackMapFrameType Low) # 
type Rep (StackMapFrame Low) # 
type Rep (StackMapFrame Low) = D1 * (MetaData "StackMapFrame" "Language.JVM.Attribute.StackMapTable" "jvm-binary-0.1.0-JJ8Rr7ERir79pQaBJvdiXV" False) (C1 * (MetaCons "StackMapFrame" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "deltaOffset") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (DeltaOffset Low))) (S1 * (MetaSel (Just Symbol "frameType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (StackMapFrameType Low)))))
type Rep (StackMapTable Low) # 
type Rep (StackMapTable Low) = D1 * (MetaData "StackMapTable" "Language.JVM.Attribute.StackMapTable" "jvm-binary-0.1.0-JJ8Rr7ERir79pQaBJvdiXV" True) (C1 * (MetaCons "StackMapTable" PrefixI True) (S1 * (MetaSel (Just Symbol "stackMapTable") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Choice (SizedList16 (StackMapFrame Low)) [StackMapFrame High] Low))))
type Rep (Signature Low) # 
type Rep (Signature Low) = D1 * (MetaData "Signature" "Language.JVM.Attribute.Signature" "jvm-binary-0.1.0-JJ8Rr7ERir79pQaBJvdiXV" False) (C1 * (MetaCons "Signature" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Ref Text Low))))
type Rep (Exceptions Low) # 
type Rep (Exceptions Low) = D1 * (MetaData "Exceptions" "Language.JVM.Attribute.Exceptions" "jvm-binary-0.1.0-JJ8Rr7ERir79pQaBJvdiXV" True) (C1 * (MetaCons "Exceptions" PrefixI True) (S1 * (MetaSel (Just Symbol "exceptions") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (SizedList16 (Ref ClassName Low)))))
type Rep (ConstantValue Low) # 
type Rep (ConstantValue Low) = D1 * (MetaData "ConstantValue" "Language.JVM.Attribute.ConstantValue" "jvm-binary-0.1.0-JJ8Rr7ERir79pQaBJvdiXV" False) (C1 * (MetaCons "ConstantValue" PrefixI True) (S1 * (MetaSel (Just Symbol "constantValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Ref JValue Low))))
type Rep (CodeAttributes Low) # 
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])))))
type Rep (ExceptionTable Low) # 
type Rep (Code Low) # 
type Rep (BootstrapMethod Low) # 
type Rep (BootstrapMethod Low) = D1 * (MetaData "BootstrapMethod" "Language.JVM.Attribute.BootstrapMethods" "jvm-binary-0.1.0-JJ8Rr7ERir79pQaBJvdiXV" False) (C1 * (MetaCons "BootstrapMethod" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "method") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (DeepRef MethodHandle Low))) (S1 * (MetaSel (Just Symbol "arguments") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (SizedList16 (Ref JValue Low))))))
type Rep (BootstrapMethods Low) # 
type Rep (BootstrapMethods Low) = D1 * (MetaData "BootstrapMethods" "Language.JVM.Attribute.BootstrapMethods" "jvm-binary-0.1.0-JJ8Rr7ERir79pQaBJvdiXV" True) (C1 * (MetaCons "BootstrapMethods" PrefixI True) (S1 * (MetaSel (Just Symbol "methods'") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (SizedList16 (BootstrapMethod Low)))))
type Rep (MethodAttributes Low) # 
type Rep (Method Low) # 
type Rep (FieldAttributes Low) # 
type Rep (FieldAttributes Low) = D1 * (MetaData "FieldAttributes" "Language.JVM.Field" "jvm-binary-0.1.0-JJ8Rr7ERir79pQaBJvdiXV" False) (C1 * (MetaCons "FieldAttributes" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "faConstantValues") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [ConstantValue Low])) ((:*:) * (S1 * (MetaSel (Just Symbol "faSignatures") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [Signature Low])) (S1 * (MetaSel (Just Symbol "faOthers") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [Attribute Low])))))
type Rep (Field Low) # 
type Rep (ClassAttributes Low) # 
type Rep (ClassAttributes Low) = D1 * (MetaData "ClassAttributes" "Language.JVM.ClassFile" "jvm-binary-0.1.0-JJ8Rr7ERir79pQaBJvdiXV" False) (C1 * (MetaCons "ClassAttributes" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "caBootstrapMethods") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [BootstrapMethods Low])) ((:*:) * (S1 * (MetaSel (Just Symbol "caSignature") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [Signature Low])) (S1 * (MetaSel (Just Symbol "caOthers") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [Attribute Low])))))
type Rep (ClassFile Low) # 
type Rep (ClassFile Low) = D1 * (MetaData "ClassFile" "Language.JVM.ClassFile" "jvm-binary-0.1.0-JJ8Rr7ERir79pQaBJvdiXV" False) (C1 * (MetaCons "ClassFile" PrefixI True) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "cMagicNumber") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Word32)) (S1 * (MetaSel (Just Symbol "cMinorVersion") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Word16))) ((:*:) * (S1 * (MetaSel (Just Symbol "cMajorVersion") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Word16)) ((:*:) * (S1 * (MetaSel (Just Symbol "cConstantPool") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Choice (ConstantPool Low) () Low))) (S1 * (MetaSel (Just Symbol "cAccessFlags'") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (BitSet16 CAccessFlag)))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "cThisClass") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Ref ClassName Low))) ((:*:) * (S1 * (MetaSel (Just Symbol "cSuperClass") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Ref ClassName Low))) (S1 * (MetaSel (Just Symbol "cInterfaces") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (SizedList16 (Ref ClassName Low)))))) ((:*:) * (S1 * (MetaSel (Just Symbol "cFields'") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (SizedList16 (Field Low)))) ((:*:) * (S1 * (MetaSel (Just Symbol "cMethods'") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (SizedList16 (Method Low)))) (S1 * (MetaSel (Just Symbol "cAttributes") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Attributes ClassAttributes Low))))))))
type Rep (InClass FieldId Low) # 
type Rep (InClass FieldId Low) = D1 * (MetaData "InClass" "Language.JVM.Constant" "jvm-binary-0.1.0-JJ8Rr7ERir79pQaBJvdiXV" False) (C1 * (MetaCons "InClass" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "inClassName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Ref ClassName Low))) (S1 * (MetaSel (Just Symbol "inClassId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Ref FieldId Low)))))
type Rep (InClass MethodId Low) # 
type Rep (InClass MethodId Low) = D1 * (MetaData "InClass" "Language.JVM.Constant" "jvm-binary-0.1.0-JJ8Rr7ERir79pQaBJvdiXV" False) (C1 * (MetaCons "InClass" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "inClassName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Ref ClassName Low))) (S1 * (MetaSel (Just Symbol "inClassId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Ref MethodId Low)))))