jvm-binary-0.10.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

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

Instances details
Staged Constant Source # 
Instance details

Defined in Language.JVM.Staged

Methods

stage :: LabelM m => (forall (s' :: Type -> Type). 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 # 
Instance details

Defined in Language.JVM.Constant

Eq (Constant Low) Source # 
Instance details

Defined in Language.JVM.Constant

Ord (Constant Low) Source # 
Instance details

Defined in Language.JVM.Constant

Show (Constant High) Source # 
Instance details

Defined in Language.JVM.Constant

Show (Constant Low) Source # 
Instance details

Defined in Language.JVM.Constant

Generic (Constant High) Source # 
Instance details

Defined in Language.JVM.Constant

Associated Types

type Rep (Constant High) :: 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 #

Binary (Constant Low) Source # 
Instance details

Defined in Language.JVM.Constant

NFData (Constant High) Source # 
Instance details

Defined in Language.JVM.Constant

Methods

rnf :: Constant High -> () #

NFData (Constant Low) Source # 
Instance details

Defined in Language.JVM.Constant

Methods

rnf :: Constant Low -> () #

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 #

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.10.0-6UZh5809b0fJPIjalFrBq2" '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 (Choice (Index, Index) AbsFieldId High))) :+: (C1 ('MetaCons "CMethodRef" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Choice (Index, Index) (InRefType MethodId) High))) :+: C1 ('MetaCons "CInterfaceMethodRef" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Choice (Index, Index) (InRefType 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 (Constant Low) Source # 
Instance details

Defined in Language.JVM.Constant

type Rep (Constant Low) = D1 ('MetaData "Constant" "Language.JVM.Constant" "jvm-binary-0.10.0-6UZh5809b0fJPIjalFrBq2" '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 (Choice (Index, Index) AbsFieldId Low))) :+: (C1 ('MetaCons "CMethodRef" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Choice (Index, Index) (InRefType MethodId) Low))) :+: C1 ('MetaCons "CInterfaceMethodRef" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Choice (Index, Index) (InRefType 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)))))))

constantSize :: Constant r -> Index 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.

Methods

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

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

Instances

Instances details
Referenceable ByteString Source # 
Instance details

Defined in Language.JVM.Constant

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 # 
Instance details

Defined in Language.JVM.Constant

Methods

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

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

Referenceable AbsFieldId Source # 
Instance details

Defined in Language.JVM.Constant

Methods

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

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

Referenceable MethodId Source # 
Instance details

Defined in Language.JVM.Constant

Methods

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

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

Referenceable FieldId Source # 
Instance details

Defined in Language.JVM.Constant

Methods

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

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

Referenceable FieldDescriptor Source # 
Instance details

Defined in Language.JVM.Constant

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 # 
Instance details

Defined in Language.JVM.Constant

Methods

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

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

Referenceable ReturnDescriptor Source # 
Instance details

Defined in Language.JVM.Constant

Methods

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

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

Referenceable JRefType Source # 
Instance details

Defined in Language.JVM.Constant

Methods

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

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

Referenceable ClassName Source # 
Instance details

Defined in Language.JVM.Constant

Methods

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

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

Referenceable AbsVariableMethodId Source # 
Instance details

Defined in Language.JVM.Constant

Methods

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

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

Referenceable AbsInterfaceMethodId Source # 
Instance details

Defined in Language.JVM.Constant

Referenceable JValue Source # 
Instance details

Defined in Language.JVM.Constant

Methods

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

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

Referenceable VDouble Source # 
Instance details

Defined in Language.JVM.Constant

Methods

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

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

Referenceable VFloat Source # 
Instance details

Defined in Language.JVM.Constant

Methods

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

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

Referenceable VLong Source # 
Instance details

Defined in Language.JVM.Constant

Methods

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

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

Referenceable VInteger Source # 
Instance details

Defined in Language.JVM.Constant

Methods

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

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

Referenceable (InRefType MethodId) Source # 
Instance details

Defined in Language.JVM.Constant

Methods

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

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

TextSerializable a => Referenceable (NameAndType a) Source # 
Instance details

Defined in Language.JVM.Constant

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 # 
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 (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 #

JValue

data JValue Source #

A constant pool value in java

Instances

Instances details
Eq JValue Source # 
Instance details

Defined in Language.JVM.Constant

Methods

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

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

Show JValue Source # 
Instance details

Defined in Language.JVM.Constant

Generic JValue Source # 
Instance details

Defined in Language.JVM.Constant

Associated Types

type Rep JValue :: Type -> Type #

Methods

from :: JValue -> Rep JValue x #

to :: Rep JValue x -> JValue #

NFData JValue Source # 
Instance details

Defined in Language.JVM.Constant

Methods

rnf :: JValue -> () #

Referenceable JValue Source # 
Instance details

Defined in Language.JVM.Constant

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 # 
Instance details

Defined in Language.JVM.Constant

Special constants

data ClassName Source #

A class name

Instances

Instances details
Eq ClassName Source # 
Instance details

Defined in Language.JVM.Type

Ord ClassName Source # 
Instance details

Defined in Language.JVM.Type

Show ClassName Source # 
Instance details

Defined in Language.JVM.Type

IsString ClassName Source # 
Instance details

Defined in Language.JVM.Type

Generic ClassName Source # 
Instance details

Defined in Language.JVM.Type

Associated Types

type Rep ClassName :: Type -> Type #

NFData ClassName Source # 
Instance details

Defined in Language.JVM.Type

Methods

rnf :: ClassName -> () #

TextSerializable ClassName Source # 
Instance details

Defined in Language.JVM.Type

Referenceable ClassName Source # 
Instance details

Defined in Language.JVM.Constant

Methods

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

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

type Rep ClassName Source # 
Instance details

Defined in Language.JVM.Type

type Rep ClassName = D1 ('MetaData "ClassName" "Language.JVM.Type" "jvm-binary-0.10.0-6UZh5809b0fJPIjalFrBq2" 'True) (C1 ('MetaCons "ClassName" 'PrefixI 'True) (S1 ('MetaSel ('Just "classNameAsText") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))

data InClass a Source #

A method or Field in a Class

Constructors

InClass 

Fields

Instances

Instances details
Eq a => Eq (InClass a) Source # 
Instance details

Defined in Language.JVM.Type

Methods

(==) :: InClass a -> InClass a -> Bool #

(/=) :: InClass a -> InClass a -> Bool #

Ord a => Ord (InClass a) Source # 
Instance details

Defined in Language.JVM.Type

Methods

compare :: InClass a -> InClass a -> Ordering #

(<) :: InClass a -> InClass a -> Bool #

(<=) :: InClass a -> InClass a -> Bool #

(>) :: InClass a -> InClass a -> Bool #

(>=) :: InClass a -> InClass a -> Bool #

max :: InClass a -> InClass a -> InClass a #

min :: InClass a -> InClass a -> InClass a #

Show a => Show (InClass a) Source # 
Instance details

Defined in Language.JVM.Type

Methods

showsPrec :: Int -> InClass a -> ShowS #

show :: InClass a -> String #

showList :: [InClass a] -> ShowS #

Generic (InClass a) Source # 
Instance details

Defined in Language.JVM.Type

Associated Types

type Rep (InClass a) :: Type -> Type #

Methods

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

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

NFData a => NFData (InClass a) Source # 
Instance details

Defined in Language.JVM.Type

Methods

rnf :: InClass a -> () #

type Rep (InClass a) Source # 
Instance details

Defined in Language.JVM.Type

type Rep (InClass a) = D1 ('MetaData "InClass" "Language.JVM.Type" "jvm-binary-0.10.0-6UZh5809b0fJPIjalFrBq2" 'False) (C1 ('MetaCons "InClass" 'PrefixI 'True) (S1 ('MetaSel ('Just "inClassName") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ClassName) :*: S1 ('MetaSel ('Just "inClassId") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 a)))

data InRefType a Source #

A method or Field in a Class

Constructors

InRefType 

Fields

Instances

Instances details
Eq a => Eq (InRefType a) Source # 
Instance details

Defined in Language.JVM.Type

Methods

(==) :: InRefType a -> InRefType a -> Bool #

(/=) :: InRefType a -> InRefType a -> Bool #

Ord a => Ord (InRefType a) Source # 
Instance details

Defined in Language.JVM.Type

Show a => Show (InRefType a) Source # 
Instance details

Defined in Language.JVM.Type

Generic (InRefType a) Source # 
Instance details

Defined in Language.JVM.Type

Associated Types

type Rep (InRefType a) :: Type -> Type #

Methods

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

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

NFData a => NFData (InRefType a) Source # 
Instance details

Defined in Language.JVM.Type

Methods

rnf :: InRefType a -> () #

Referenceable (InRefType MethodId) Source # 
Instance details

Defined in Language.JVM.Constant

Methods

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

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

type Rep (InRefType a) Source # 
Instance details

Defined in Language.JVM.Type

type Rep (InRefType a) = D1 ('MetaData "InRefType" "Language.JVM.Type" "jvm-binary-0.10.0-6UZh5809b0fJPIjalFrBq2" 'False) (C1 ('MetaCons "InRefType" 'PrefixI 'True) (S1 ('MetaSel ('Just "inRefType") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 JRefType) :*: S1 ('MetaSel ('Just "inRefTypeId") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 a)))

newtype AbsFieldId Source #

A FieldId

Instances

Instances details
Eq AbsFieldId Source # 
Instance details

Defined in Language.JVM.Type

Ord AbsFieldId Source # 
Instance details

Defined in Language.JVM.Type

Show AbsFieldId Source # 
Instance details

Defined in Language.JVM.Type

IsString AbsFieldId Source # 
Instance details

Defined in Language.JVM.Type

Generic AbsFieldId Source # 
Instance details

Defined in Language.JVM.Type

Associated Types

type Rep AbsFieldId :: Type -> Type #

NFData AbsFieldId Source # 
Instance details

Defined in Language.JVM.Type

Methods

rnf :: AbsFieldId -> () #

TextSerializable AbsFieldId Source # 
Instance details

Defined in Language.JVM.Type

Referenceable AbsFieldId Source # 
Instance details

Defined in Language.JVM.Constant

Methods

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

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

type Rep AbsFieldId Source # 
Instance details

Defined in Language.JVM.Type

type Rep AbsFieldId = D1 ('MetaData "AbsFieldId" "Language.JVM.Type" "jvm-binary-0.10.0-6UZh5809b0fJPIjalFrBq2" 'True) (C1 ('MetaCons "AbsFieldId" 'PrefixI 'True) (S1 ('MetaSel ('Just "absFieldAsInClass") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (InClass FieldId))))

newtype AbsInterfaceMethodId Source #

An method which is from an interface

Instances

Instances details
Eq AbsInterfaceMethodId Source # 
Instance details

Defined in Language.JVM.Constant

Show AbsInterfaceMethodId Source # 
Instance details

Defined in Language.JVM.Constant

Generic AbsInterfaceMethodId Source # 
Instance details

Defined in Language.JVM.Constant

Associated Types

type Rep AbsInterfaceMethodId :: Type -> Type #

NFData AbsInterfaceMethodId Source # 
Instance details

Defined in Language.JVM.Constant

Methods

rnf :: AbsInterfaceMethodId -> () #

Referenceable AbsInterfaceMethodId Source # 
Instance details

Defined in Language.JVM.Constant

type Rep AbsInterfaceMethodId Source # 
Instance details

Defined in Language.JVM.Constant

type Rep AbsInterfaceMethodId = D1 ('MetaData "AbsInterfaceMethodId" "Language.JVM.Constant" "jvm-binary-0.10.0-6UZh5809b0fJPIjalFrBq2" 'True) (C1 ('MetaCons "AbsInterfaceMethodId" 'PrefixI 'True) (S1 ('MetaSel ('Just "interfaceMethodId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (InRefType MethodId))))

data AbsVariableMethodId Source #

An method which can be from an interface

Instances

Instances details
Eq AbsVariableMethodId Source # 
Instance details

Defined in Language.JVM.Constant

Show AbsVariableMethodId Source # 
Instance details

Defined in Language.JVM.Constant

Generic AbsVariableMethodId Source # 
Instance details

Defined in Language.JVM.Constant

Associated Types

type Rep AbsVariableMethodId :: Type -> Type #

NFData AbsVariableMethodId Source # 
Instance details

Defined in Language.JVM.Constant

Methods

rnf :: AbsVariableMethodId -> () #

Referenceable AbsVariableMethodId Source # 
Instance details

Defined in Language.JVM.Constant

Methods

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

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

type Rep AbsVariableMethodId Source # 
Instance details

Defined in Language.JVM.Constant

type Rep AbsVariableMethodId = D1 ('MetaData "AbsVariableMethodId" "Language.JVM.Constant" "jvm-binary-0.10.0-6UZh5809b0fJPIjalFrBq2" 'False) (C1 ('MetaCons "AbsVariableMethodId" 'PrefixI 'True) (S1 ('MetaSel ('Just "variableIsInterface") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bool) :*: S1 ('MetaSel ('Just "variableMethodId") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (InRefType MethodId))))

newtype MethodId Source #

A MethodId

Instances

Instances details
Eq MethodId Source # 
Instance details

Defined in Language.JVM.Type

Ord MethodId Source # 
Instance details

Defined in Language.JVM.Type

Show MethodId Source # 
Instance details

Defined in Language.JVM.Type

IsString MethodId Source # 
Instance details

Defined in Language.JVM.Type

Generic MethodId Source # 
Instance details

Defined in Language.JVM.Type

Associated Types

type Rep MethodId :: Type -> Type #

Methods

from :: MethodId -> Rep MethodId x #

to :: Rep MethodId x -> MethodId #

NFData MethodId Source # 
Instance details

Defined in Language.JVM.Type

Methods

rnf :: MethodId -> () #

TextSerializable MethodId Source # 
Instance details

Defined in Language.JVM.Type

AsNameAndType MethodId Source # 
Instance details

Defined in Language.JVM.Type

Associated Types

type TypeDescriptor MethodId Source #

Referenceable MethodId Source # 
Instance details

Defined in Language.JVM.Constant

Methods

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

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

Referenceable (InRefType MethodId) Source # 
Instance details

Defined in Language.JVM.Constant

Methods

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

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

type Rep MethodId Source # 
Instance details

Defined in Language.JVM.Type

type Rep MethodId = D1 ('MetaData "MethodId" "Language.JVM.Type" "jvm-binary-0.10.0-6UZh5809b0fJPIjalFrBq2" 'True) (C1 ('MetaCons "MethodId" 'PrefixI 'True) (S1 ('MetaSel ('Just "methodIdAsNameAndType") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (NameAndType MethodDescriptor))))
type TypeDescriptor MethodId Source # 
Instance details

Defined in Language.JVM.Type

newtype FieldId Source #

A FieldId

Instances

Instances details
Eq FieldId Source # 
Instance details

Defined in Language.JVM.Type

Methods

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

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

Ord FieldId Source # 
Instance details

Defined in Language.JVM.Type

Show FieldId Source # 
Instance details

Defined in Language.JVM.Type

IsString FieldId Source # 
Instance details

Defined in Language.JVM.Type

Methods

fromString :: String -> FieldId #

Generic FieldId Source # 
Instance details

Defined in Language.JVM.Type

Associated Types

type Rep FieldId :: Type -> Type #

Methods

from :: FieldId -> Rep FieldId x #

to :: Rep FieldId x -> FieldId #

NFData FieldId Source # 
Instance details

Defined in Language.JVM.Type

Methods

rnf :: FieldId -> () #

TextSerializable FieldId Source # 
Instance details

Defined in Language.JVM.Type

AsNameAndType FieldId Source # 
Instance details

Defined in Language.JVM.Type

Associated Types

type TypeDescriptor FieldId Source #

Referenceable FieldId Source # 
Instance details

Defined in Language.JVM.Constant

Methods

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

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

type Rep FieldId Source # 
Instance details

Defined in Language.JVM.Type

type Rep FieldId = D1 ('MetaData "FieldId" "Language.JVM.Type" "jvm-binary-0.10.0-6UZh5809b0fJPIjalFrBq2" 'True) (C1 ('MetaCons "FieldId" 'PrefixI 'True) (S1 ('MetaSel ('Just "fieldIdAsNameAndType") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (NameAndType FieldDescriptor))))
type TypeDescriptor FieldId Source # 
Instance details

Defined in Language.JVM.Type

data NameAndType a Source #

A name and a type

Constructors

NameAndType !Text !a 

Instances

Instances details
Eq a => Eq (NameAndType a) Source # 
Instance details

Defined in Language.JVM.Type

Ord a => Ord (NameAndType a) Source # 
Instance details

Defined in Language.JVM.Type

Show a => Show (NameAndType a) Source # 
Instance details

Defined in Language.JVM.Type

Generic (NameAndType a) Source # 
Instance details

Defined in Language.JVM.Type

Associated Types

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

Methods

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

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

NFData a => NFData (NameAndType a) Source # 
Instance details

Defined in Language.JVM.Type

Methods

rnf :: NameAndType a -> () #

AsNameAndType (NameAndType a) Source # 
Instance details

Defined in Language.JVM.Type

Associated Types

type TypeDescriptor (NameAndType a) Source #

TextSerializable a => Referenceable (NameAndType a) Source # 
Instance details

Defined in Language.JVM.Constant

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 # 
Instance details

Defined in Language.JVM.Type

type Rep (NameAndType a) = D1 ('MetaData "NameAndType" "Language.JVM.Type" "jvm-binary-0.10.0-6UZh5809b0fJPIjalFrBq2" 'False) (C1 ('MetaCons "NameAndType" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 a)))
type TypeDescriptor (NameAndType a) Source # 
Instance details

Defined in Language.JVM.Type

data MethodDescriptor Source #

Method Descriptor

Instances

Instances details
Eq MethodDescriptor Source # 
Instance details

Defined in Language.JVM.Type

Ord MethodDescriptor Source # 
Instance details

Defined in Language.JVM.Type

Show MethodDescriptor Source # 
Instance details

Defined in Language.JVM.Type

IsString MethodDescriptor Source # 
Instance details

Defined in Language.JVM.Type

Generic MethodDescriptor Source # 
Instance details

Defined in Language.JVM.Type

Associated Types

type Rep MethodDescriptor :: Type -> Type #

NFData MethodDescriptor Source # 
Instance details

Defined in Language.JVM.Type

Methods

rnf :: MethodDescriptor -> () #

TextSerializable MethodDescriptor Source # 
Instance details

Defined in Language.JVM.Type

WithName MethodDescriptor Source # 
Instance details

Defined in Language.JVM.Type

Associated Types

type WithNameId MethodDescriptor Source #

Referenceable MethodDescriptor Source # 
Instance details

Defined in Language.JVM.Constant

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 # 
Instance details

Defined in Language.JVM.Type

type Rep MethodDescriptor = D1 ('MetaData "MethodDescriptor" "Language.JVM.Type" "jvm-binary-0.10.0-6UZh5809b0fJPIjalFrBq2" 'False) (C1 ('MetaCons "MethodDescriptor" 'PrefixI 'True) (S1 ('MetaSel ('Just "methodDescriptorArguments") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [JType]) :*: S1 ('MetaSel ('Just "methodDescriptorReturnType") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ReturnDescriptor)))
type WithNameId MethodDescriptor Source # 
Instance details

Defined in Language.JVM.Type

data FieldDescriptor Source #

Field Descriptor

Instances

Instances details
Eq FieldDescriptor Source # 
Instance details

Defined in Language.JVM.Type

Ord FieldDescriptor Source # 
Instance details

Defined in Language.JVM.Type

Show FieldDescriptor Source # 
Instance details

Defined in Language.JVM.Type

IsString FieldDescriptor Source # 
Instance details

Defined in Language.JVM.Type

Generic FieldDescriptor Source # 
Instance details

Defined in Language.JVM.Type

Associated Types

type Rep FieldDescriptor :: Type -> Type #

NFData FieldDescriptor Source # 
Instance details

Defined in Language.JVM.Type

Methods

rnf :: FieldDescriptor -> () #

TextSerializable FieldDescriptor Source # 
Instance details

Defined in Language.JVM.Type

WithName FieldDescriptor Source # 
Instance details

Defined in Language.JVM.Type

Associated Types

type WithNameId FieldDescriptor Source #

Referenceable FieldDescriptor Source # 
Instance details

Defined in Language.JVM.Constant

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 # 
Instance details

Defined in Language.JVM.Type

type Rep FieldDescriptor = D1 ('MetaData "FieldDescriptor" "Language.JVM.Type" "jvm-binary-0.10.0-6UZh5809b0fJPIjalFrBq2" 'True) (C1 ('MetaCons "FieldDescriptor" 'PrefixI 'True) (S1 ('MetaSel ('Just "fieldDescriptorType") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 JType)))
type WithNameId FieldDescriptor Source # 
Instance details

Defined in Language.JVM.Type

data MethodHandle r Source #

The union type over the different method handles.

Instances

Instances details
Staged MethodHandle Source # 
Instance details

Defined in Language.JVM.Staged

Methods

stage :: LabelM m => (forall (s' :: Type -> Type). 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 # 
Instance details

Defined in Language.JVM.Constant

Eq (MethodHandle Low) Source # 
Instance details

Defined in Language.JVM.Constant

Ord (MethodHandle Low) Source # 
Instance details

Defined in Language.JVM.Constant

Show (MethodHandle High) Source # 
Instance details

Defined in Language.JVM.Constant

Show (MethodHandle Low) Source # 
Instance details

Defined in Language.JVM.Constant

Generic (MethodHandle High) Source # 
Instance details

Defined in Language.JVM.Constant

Associated Types

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

Generic (MethodHandle Low) Source # 
Instance details

Defined in Language.JVM.Constant

Associated Types

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

Binary (MethodHandle Low) Source # 
Instance details

Defined in Language.JVM.Constant

NFData (MethodHandle High) Source # 
Instance details

Defined in Language.JVM.Constant

Methods

rnf :: MethodHandle High -> () #

NFData (MethodHandle Low) Source # 
Instance details

Defined in Language.JVM.Constant

Methods

rnf :: MethodHandle Low -> () #

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 #

type Rep (MethodHandle High) Source # 
Instance details

Defined in Language.JVM.Constant

type Rep (MethodHandle Low) Source # 
Instance details

Defined in Language.JVM.Constant

data MethodHandleField r Source #

Instances

Instances details
Staged MethodHandleField Source # 
Instance details

Defined in Language.JVM.Staged

Methods

stage :: LabelM m => (forall (s' :: Type -> Type). 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 # 
Instance details

Defined in Language.JVM.Constant

Eq (MethodHandleField Low) Source # 
Instance details

Defined in Language.JVM.Constant

Ord (MethodHandleField Low) Source # 
Instance details

Defined in Language.JVM.Constant

Show (MethodHandleField High) Source # 
Instance details

Defined in Language.JVM.Constant

Show (MethodHandleField Low) Source # 
Instance details

Defined in Language.JVM.Constant

Generic (MethodHandleField High) Source # 
Instance details

Defined in Language.JVM.Constant

Associated Types

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

Generic (MethodHandleField Low) Source # 
Instance details

Defined in Language.JVM.Constant

Associated Types

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

NFData (MethodHandleField High) Source # 
Instance details

Defined in Language.JVM.Constant

Methods

rnf :: MethodHandleField High -> () #

NFData (MethodHandleField Low) Source # 
Instance details

Defined in Language.JVM.Constant

Methods

rnf :: MethodHandleField Low -> () #

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.10.0-6UZh5809b0fJPIjalFrBq2" 'False) (C1 ('MetaCons "MethodHandleField" 'PrefixI 'True) (S1 ('MetaSel ('Just "methodHandleFieldKind") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 MethodHandleFieldKind) :*: S1 ('MetaSel ('Just "methodHandleFieldRef") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Ref AbsFieldId High))))
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.10.0-6UZh5809b0fJPIjalFrBq2" 'False) (C1 ('MetaCons "MethodHandleField" 'PrefixI 'True) (S1 ('MetaSel ('Just "methodHandleFieldKind") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 MethodHandleFieldKind) :*: S1 ('MetaSel ('Just "methodHandleFieldRef") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Ref AbsFieldId Low))))

data MethodHandleMethod r Source #

Instances

Instances details
Staged MethodHandleMethod Source # 
Instance details

Defined in Language.JVM.Staged

Eq (MethodHandleMethod High) Source # 
Instance details

Defined in Language.JVM.Constant

Eq (MethodHandleMethod Low) Source # 
Instance details

Defined in Language.JVM.Constant

Ord (MethodHandleMethod Low) Source # 
Instance details

Defined in Language.JVM.Constant

Show (MethodHandleMethod High) Source # 
Instance details

Defined in Language.JVM.Constant

Show (MethodHandleMethod Low) Source # 
Instance details

Defined in Language.JVM.Constant

Generic (MethodHandleMethod High) Source # 
Instance details

Defined in Language.JVM.Constant

Associated Types

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

Generic (MethodHandleMethod Low) Source # 
Instance details

Defined in Language.JVM.Constant

Associated Types

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

NFData (MethodHandleMethod High) Source # 
Instance details

Defined in Language.JVM.Constant

Methods

rnf :: MethodHandleMethod High -> () #

NFData (MethodHandleMethod Low) Source # 
Instance details

Defined in Language.JVM.Constant

Methods

rnf :: MethodHandleMethod Low -> () #

type Rep (MethodHandleMethod High) Source # 
Instance details

Defined in Language.JVM.Constant

type Rep (MethodHandleMethod Low) Source # 
Instance details

Defined in Language.JVM.Constant

newtype MethodHandleInterface r Source #

Instances

Instances details
Staged MethodHandleInterface Source # 
Instance details

Defined in Language.JVM.Staged

Eq (MethodHandleInterface High) Source # 
Instance details

Defined in Language.JVM.Constant

Eq (MethodHandleInterface Low) Source # 
Instance details

Defined in Language.JVM.Constant

Ord (MethodHandleInterface Low) Source # 
Instance details

Defined in Language.JVM.Constant

Show (MethodHandleInterface High) Source # 
Instance details

Defined in Language.JVM.Constant

Show (MethodHandleInterface Low) Source # 
Instance details

Defined in Language.JVM.Constant

Generic (MethodHandleInterface High) Source # 
Instance details

Defined in Language.JVM.Constant

Associated Types

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

Generic (MethodHandleInterface Low) Source # 
Instance details

Defined in Language.JVM.Constant

Associated Types

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

NFData (MethodHandleInterface High) Source # 
Instance details

Defined in Language.JVM.Constant

NFData (MethodHandleInterface Low) Source # 
Instance details

Defined in Language.JVM.Constant

Methods

rnf :: MethodHandleInterface Low -> () #

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.10.0-6UZh5809b0fJPIjalFrBq2" 'True) (C1 ('MetaCons "MethodHandleInterface" 'PrefixI 'True) (S1 ('MetaSel ('Just "methodHandleInterfaceRef") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Ref AbsInterfaceMethodId High))))
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.10.0-6UZh5809b0fJPIjalFrBq2" 'True) (C1 ('MetaCons "MethodHandleInterface" 'PrefixI 'True) (S1 ('MetaSel ('Just "methodHandleInterfaceRef") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Ref AbsInterfaceMethodId Low))))

data MethodHandleFieldKind Source #

Instances

Instances details
Eq MethodHandleFieldKind Source # 
Instance details

Defined in Language.JVM.Constant

Ord MethodHandleFieldKind Source # 
Instance details

Defined in Language.JVM.Constant

Show MethodHandleFieldKind Source # 
Instance details

Defined in Language.JVM.Constant

Generic MethodHandleFieldKind Source # 
Instance details

Defined in Language.JVM.Constant

Associated Types

type Rep MethodHandleFieldKind :: Type -> Type #

NFData MethodHandleFieldKind Source # 
Instance details

Defined in Language.JVM.Constant

Methods

rnf :: MethodHandleFieldKind -> () #

type Rep MethodHandleFieldKind Source # 
Instance details

Defined in Language.JVM.Constant

type Rep MethodHandleFieldKind = D1 ('MetaData "MethodHandleFieldKind" "Language.JVM.Constant" "jvm-binary-0.10.0-6UZh5809b0fJPIjalFrBq2" 'False) ((C1 ('MetaCons "MHGetField" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MHGetStatic" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "MHPutField" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MHPutStatic" 'PrefixI 'False) (U1 :: Type -> Type)))

data InvokeDynamic r Source #

Instances

Instances details
Staged InvokeDynamic Source # 
Instance details

Defined in Language.JVM.Staged

Methods

stage :: LabelM m => (forall (s' :: Type -> Type). 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 # 
Instance details

Defined in Language.JVM.Constant

Eq (InvokeDynamic Low) Source # 
Instance details

Defined in Language.JVM.Constant

Ord (InvokeDynamic Low) Source # 
Instance details

Defined in Language.JVM.Constant

Show (InvokeDynamic High) Source # 
Instance details

Defined in Language.JVM.Constant

Show (InvokeDynamic Low) Source # 
Instance details

Defined in Language.JVM.Constant

Generic (InvokeDynamic High) Source # 
Instance details

Defined in Language.JVM.Constant

Associated Types

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

Generic (InvokeDynamic Low) Source # 
Instance details

Defined in Language.JVM.Constant

Associated Types

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

Binary (InvokeDynamic Low) Source # 
Instance details

Defined in Language.JVM.Constant

NFData (InvokeDynamic High) Source # 
Instance details

Defined in Language.JVM.Constant

Methods

rnf :: InvokeDynamic High -> () #

NFData (InvokeDynamic Low) Source # 
Instance details

Defined in Language.JVM.Constant

Methods

rnf :: InvokeDynamic Low -> () #

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 #

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.10.0-6UZh5809b0fJPIjalFrBq2" '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 (InvokeDynamic Low) Source # 
Instance details

Defined in Language.JVM.Constant

type Rep (InvokeDynamic Low) = D1 ('MetaData "InvokeDynamic" "Language.JVM.Constant" "jvm-binary-0.10.0-6UZh5809b0fJPIjalFrBq2" '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))))

re-exports

data High Source #

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

Instances

Instances details
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 (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 (BootstrapMethod High) Source # 
Instance details

Defined in Language.JVM.Attribute.BootstrapMethods

Eq (BootstrapMethods High) Source # 
Instance details

Defined in Language.JVM.Attribute.BootstrapMethods

Eq (AnnotationDefault High) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Eq (TypeArgumentTarget High) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Eq (LocalvarEntry High) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Eq (CodeTypeAnnotation High) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Eq (FieldTypeAnnotation High) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Eq (MethodTypeAnnotation High) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Eq (ClassTypeAnnotation High) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Eq (EnumValue High) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Eq (ElementValue High) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Eq (ValuePair High) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Eq (Annotation High) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Eq (RuntimeInvisibleParameterAnnotations High) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Eq (RuntimeVisibleParameterAnnotations High) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Eq (RuntimeInvisibleAnnotations High) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Eq (RuntimeVisibleAnnotations High) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

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 (MethodParameter High) Source # 
Instance details

Defined in Language.JVM.Attribute.MethodParameters

Eq (MethodParameters High) Source # 
Instance details

Defined in Language.JVM.Attribute.MethodParameters

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

Ord (TypeArgumentTarget High) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Ord (LocalvarEntry High) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Ord (CodeTypeAnnotation High) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Ord (FieldTypeAnnotation High) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Ord (MethodTypeAnnotation High) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Ord (ClassTypeAnnotation High) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Ord (EnumValue High) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Ord (ElementValue High) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Ord (ValuePair High) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Ord (Annotation High) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

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 (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 (BootstrapMethod High) Source # 
Instance details

Defined in Language.JVM.Attribute.BootstrapMethods

Show (BootstrapMethods High) Source # 
Instance details

Defined in Language.JVM.Attribute.BootstrapMethods

Show (AnnotationDefault High) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Show (TypeArgumentTarget High) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Show (LocalvarEntry High) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Show (CodeTypeAnnotation High) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Show (FieldTypeAnnotation High) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Show (MethodTypeAnnotation High) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Show (ClassTypeAnnotation High) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Show (EnumValue High) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Show (ElementValue High) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Show (ValuePair High) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Show (Annotation High) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Show (RuntimeInvisibleParameterAnnotations High) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Show (RuntimeVisibleParameterAnnotations High) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Show (RuntimeInvisibleAnnotations High) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Show (RuntimeVisibleAnnotations High) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

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 (MethodParameter High) Source # 
Instance details

Defined in Language.JVM.Attribute.MethodParameters

Show (MethodParameters High) Source # 
Instance details

Defined in Language.JVM.Attribute.MethodParameters

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 (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 (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 (AnnotationDefault High) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Associated Types

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

Generic (TypeArgumentTarget High) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Associated Types

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

Generic (LocalvarEntry High) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Associated Types

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

Generic (CodeTypeAnnotation High) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Associated Types

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

Generic (FieldTypeAnnotation High) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Associated Types

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

Generic (MethodTypeAnnotation High) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Associated Types

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

Generic (ClassTypeAnnotation High) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Associated Types

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

Generic (EnumValue High) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Associated Types

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

Generic (ElementValue High) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Associated Types

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

Generic (ValuePair High) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Associated Types

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

Generic (Annotation High) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Associated Types

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

Generic (RuntimeInvisibleParameterAnnotations High) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Generic (RuntimeVisibleParameterAnnotations High) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Associated Types

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

Generic (RuntimeInvisibleAnnotations High) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Associated Types

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

Generic (RuntimeVisibleAnnotations High) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Associated Types

type Rep (RuntimeVisibleAnnotations 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 (MethodParameter High) Source # 
Instance details

Defined in Language.JVM.Attribute.MethodParameters

Associated Types

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

Generic (MethodParameters High) Source # 
Instance details

Defined in Language.JVM.Attribute.MethodParameters

Associated Types

type Rep (MethodParameters 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 (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 (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 (AnnotationDefault High) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Methods

rnf :: AnnotationDefault High -> () #

NFData (TypeArgumentTarget High) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Methods

rnf :: TypeArgumentTarget High -> () #

NFData (LocalvarEntry High) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Methods

rnf :: LocalvarEntry High -> () #

NFData (CodeTypeAnnotation High) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Methods

rnf :: CodeTypeAnnotation High -> () #

NFData (FieldTypeAnnotation High) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Methods

rnf :: FieldTypeAnnotation High -> () #

NFData (MethodTypeAnnotation High) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Methods

rnf :: MethodTypeAnnotation High -> () #

NFData (ClassTypeAnnotation High) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Methods

rnf :: ClassTypeAnnotation High -> () #

NFData (EnumValue High) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Methods

rnf :: EnumValue High -> () #

NFData (ElementValue High) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Methods

rnf :: ElementValue High -> () #

NFData (ValuePair High) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Methods

rnf :: ValuePair High -> () #

NFData (Annotation High) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Methods

rnf :: Annotation High -> () #

NFData (RuntimeInvisibleParameterAnnotations High) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

NFData (RuntimeVisibleParameterAnnotations High) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

NFData (RuntimeInvisibleAnnotations High) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

NFData (RuntimeVisibleAnnotations High) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

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 (MethodParameter High) Source # 
Instance details

Defined in Language.JVM.Attribute.MethodParameters

Methods

rnf :: MethodParameter High -> () #

NFData (MethodParameters High) Source # 
Instance details

Defined in Language.JVM.Attribute.MethodParameters

Methods

rnf :: MethodParameters 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 (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 (m High) => Eq (RuntimeInvisibleTypeAnnotations m High) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Eq (m High) => Eq (RuntimeVisibleTypeAnnotations m High) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Eq (m High) => Eq (TypeAnnotation m High) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Ord (a High) => Ord (TypeAnnotation a High) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Show (m High) => Show (RuntimeInvisibleTypeAnnotations m High) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Show (m High) => Show (RuntimeVisibleTypeAnnotations m High) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Show (m High) => Show (TypeAnnotation m High) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Generic (m High) => Generic (RuntimeInvisibleTypeAnnotations m High) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Associated Types

type Rep (RuntimeInvisibleTypeAnnotations m High) :: Type -> Type #

Generic (m High) => Generic (RuntimeVisibleTypeAnnotations m High) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Associated Types

type Rep (RuntimeVisibleTypeAnnotations m High) :: Type -> Type #

Generic (m High) => Generic (TypeAnnotation m High) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Associated Types

type Rep (TypeAnnotation m High) :: Type -> Type #

(Generic (m High), NFData (m High)) => NFData (RuntimeInvisibleTypeAnnotations m High) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

(Generic (m High), NFData (m High)) => NFData (RuntimeVisibleTypeAnnotations m High) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

(Generic (m High), NFData (m High)) => NFData (TypeAnnotation m High) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Methods

rnf :: TypeAnnotation m High -> () #

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.10.0-6UZh5809b0fJPIjalFrBq2" '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.10.0-6UZh5809b0fJPIjalFrBq2" 'True) (C1 ('MetaCons "MethodHandleInterface" 'PrefixI 'True) (S1 ('MetaSel ('Just "methodHandleInterfaceRef") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Ref 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.10.0-6UZh5809b0fJPIjalFrBq2" 'False) (C1 ('MetaCons "MethodHandleField" 'PrefixI 'True) (S1 ('MetaSel ('Just "methodHandleFieldKind") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 MethodHandleFieldKind) :*: S1 ('MetaSel ('Just "methodHandleFieldRef") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Ref AbsFieldId High))))
type Rep (MethodHandle High) Source # 
Instance details

Defined in Language.JVM.Constant

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.10.0-6UZh5809b0fJPIjalFrBq2" '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 (Choice (Index, Index) AbsFieldId High))) :+: (C1 ('MetaCons "CMethodRef" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Choice (Index, Index) (InRefType MethodId) High))) :+: C1 ('MetaCons "CInterfaceMethodRef" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Choice (Index, Index) (InRefType 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.10.0-6UZh5809b0fJPIjalFrBq2" '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 (ByteCodeOpr High) = D1 ('MetaData "ByteCodeOpr" "Language.JVM.ByteCode" "jvm-binary-0.10.0-6UZh5809b0fJPIjalFrBq2" 'False) (((((C1 ('MetaCons "ArrayLoad" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ArrayType)) :+: C1 ('MetaCons "ArrayStore" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ArrayType))) :+: (C1 ('MetaCons "Push" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (BConstant High))) :+: C1 ('MetaCons "Load" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 LocalType) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 LocalAddress)))) :+: ((C1 ('MetaCons "Store" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 LocalType) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 LocalAddress)) :+: C1 ('MetaCons "BinaryOpr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 BinOpr) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ArithmeticType))) :+: (C1 ('MetaCons "Neg" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ArithmeticType)) :+: (C1 ('MetaCons "BitOpr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 BitOpr) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 WordSize)) :+: C1 ('MetaCons "IncrLocal" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 LocalAddress) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 IncrementAmount)))))) :+: (((C1 ('MetaCons "Cast" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 CastOpr)) :+: C1 ('MetaCons "CompareLongs" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "CompareFloating" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bool) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 WordSize)) :+: C1 ('MetaCons "If" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 CmpOpr) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 OneOrTwo) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (ShortRelativeRef High)))))) :+: ((C1 ('MetaCons "IfRef" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bool) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 OneOrTwo) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (ShortRelativeRef High)))) :+: C1 ('MetaCons "Goto" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (LongRelativeRef High)))) :+: (C1 ('MetaCons "Jsr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (LongRelativeRef High))) :+: (C1 ('MetaCons "Ret" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 LocalAddress)) :+: C1 ('MetaCons "TableSwitch" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (LongRelativeRef High)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (SwitchTable High)))))))) :+: ((((C1 ('MetaCons "LookupSwitch" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (LongRelativeRef High)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Vector (Int32, LongRelativeRef High)))) :+: C1 ('MetaCons "Get" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 FieldAccess) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Ref AbsFieldId High)))) :+: (C1 ('MetaCons "Put" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 FieldAccess) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Ref AbsFieldId High))) :+: C1 ('MetaCons "Invoke" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Invocation High))))) :+: ((C1 ('MetaCons "New" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Ref ClassName High))) :+: C1 ('MetaCons "NewArray" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Choice LowNewArrayType NewArrayType High)))) :+: (C1 ('MetaCons "ArrayLength" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Throw" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CheckCast" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Ref JRefType High))))))) :+: (((C1 ('MetaCons "InstanceOf" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Ref JRefType High))) :+: C1 ('MetaCons "Monitor" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bool))) :+: (C1 ('MetaCons "Return" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe LocalType))) :+: C1 ('MetaCons "Nop" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "Pop" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 WordSize)) :+: C1 ('MetaCons "Dup" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 WordSize))) :+: (C1 ('MetaCons "DupX1" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 WordSize)) :+: (C1 ('MetaCons "DupX2" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 WordSize)) :+: C1 ('MetaCons "Swap" 'PrefixI 'False) (U1 :: Type -> Type)))))))
type Rep (SwitchTable High) Source # 
Instance details

Defined in Language.JVM.ByteCode

type Rep (SwitchTable High) = D1 ('MetaData "SwitchTable" "Language.JVM.ByteCode" "jvm-binary-0.10.0-6UZh5809b0fJPIjalFrBq2" 'False) (C1 ('MetaCons "SwitchTable" 'PrefixI 'True) (S1 ('MetaSel ('Just "switchLow") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Int32) :*: S1 ('MetaSel ('Just "switchOffsets") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Vector (LongRelativeRef High)))))
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.10.0-6UZh5809b0fJPIjalFrBq2" '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.10.0-6UZh5809b0fJPIjalFrBq2" '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.10.0-6UZh5809b0fJPIjalFrBq2" '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.10.0-6UZh5809b0fJPIjalFrBq2" '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.10.0-6UZh5809b0fJPIjalFrBq2" '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 'SourceStrict 'DecidedStrict) (Rec0 (Ref JRefType High))) :+: C1 ('MetaCons "VTUninitialized" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (ByteCodeRef High)))))))
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.10.0-6UZh5809b0fJPIjalFrBq2" '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.10.0-6UZh5809b0fJPIjalFrBq2" '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.10.0-6UZh5809b0fJPIjalFrBq2" '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.10.0-6UZh5809b0fJPIjalFrBq2" '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.10.0-6UZh5809b0fJPIjalFrBq2" '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.10.0-6UZh5809b0fJPIjalFrBq2" 'True) (C1 ('MetaCons "ConstantValue" 'PrefixI 'True) (S1 ('MetaSel ('Just "constantValue") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Ref JValue High))))
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.10.0-6UZh5809b0fJPIjalFrBq2" '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.10.0-6UZh5809b0fJPIjalFrBq2" 'True) (C1 ('MetaCons "BootstrapMethods" 'PrefixI 'True) (S1 ('MetaSel ('Just "methods'") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SizedList16 (BootstrapMethod High)))))
type Rep (AnnotationDefault High) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

type Rep (AnnotationDefault High) = D1 ('MetaData "AnnotationDefault" "Language.JVM.Attribute.Annotations" "jvm-binary-0.10.0-6UZh5809b0fJPIjalFrBq2" 'True) (C1 ('MetaCons "AnnotationDefault" 'PrefixI 'True) (S1 ('MetaSel ('Just "defaultValue") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (ElementValue High))))
type Rep (TypeArgumentTarget High) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

type Rep (TypeArgumentTarget High) = D1 ('MetaData "TypeArgumentTarget" "Language.JVM.Attribute.Annotations" "jvm-binary-0.10.0-6UZh5809b0fJPIjalFrBq2" 'False) (C1 ('MetaCons "TypeArgumentTarget" 'PrefixI 'True) (S1 ('MetaSel ('Just "typeArgumentOffset") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (ByteCodeRef High)) :*: S1 ('MetaSel ('Just "typeArgumentIndex") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word8)))
type Rep (LocalvarEntry High) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

type Rep (LocalvarEntry High) = D1 ('MetaData "LocalvarEntry" "Language.JVM.Attribute.Annotations" "jvm-binary-0.10.0-6UZh5809b0fJPIjalFrBq2" 'False) (C1 ('MetaCons "LocalvarEntry" 'PrefixI 'True) (S1 ('MetaSel ('Just "lvStartPc") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (ByteCodeRef High)) :*: (S1 ('MetaSel ('Just "lvLength") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Word16) :*: S1 ('MetaSel ('Just "lvLocalVarIndex") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Word16))))
type Rep (CodeTypeAnnotation High) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

type Rep (CodeTypeAnnotation High) = D1 ('MetaData "CodeTypeAnnotation" "Language.JVM.Attribute.Annotations" "jvm-binary-0.10.0-6UZh5809b0fJPIjalFrBq2" 'False) (((C1 ('MetaCons "LocalVariableDeclaration" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (LocalvarTarget High))) :+: (C1 ('MetaCons "ResourceVariableDeclaration" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (LocalvarTarget High))) :+: C1 ('MetaCons "ExceptionParameterDeclaration" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 CatchTarget)))) :+: (C1 ('MetaCons "InstanceOfExpression" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (OffsetTarget High))) :+: (C1 ('MetaCons "NewExpression" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (OffsetTarget High))) :+: C1 ('MetaCons "NewMethodReferenceExpression" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (OffsetTarget High)))))) :+: ((C1 ('MetaCons "IdentifierMethodReferenceExpression" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (OffsetTarget High))) :+: (C1 ('MetaCons "CastExpression" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (TypeArgumentTarget High))) :+: C1 ('MetaCons "ConstructorExpression" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (TypeArgumentTarget High))))) :+: (C1 ('MetaCons "MethodIncovationExpression" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (TypeArgumentTarget High))) :+: (C1 ('MetaCons "GenericNewMethodReferenceExpression" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (TypeArgumentTarget High))) :+: C1 ('MetaCons "GenericIdentifierwMethodReferenceExpression" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (TypeArgumentTarget High)))))))
type Rep (FieldTypeAnnotation High) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

type Rep (FieldTypeAnnotation High) = D1 ('MetaData "FieldTypeAnnotation" "Language.JVM.Attribute.Annotations" "jvm-binary-0.10.0-6UZh5809b0fJPIjalFrBq2" 'False) (C1 ('MetaCons "FieldTypeAnnotation" 'PrefixI 'False) (U1 :: Type -> Type))
type Rep (MethodTypeAnnotation High) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

type Rep (MethodTypeAnnotation High) = D1 ('MetaData "MethodTypeAnnotation" "Language.JVM.Attribute.Annotations" "jvm-binary-0.10.0-6UZh5809b0fJPIjalFrBq2" 'False) ((C1 ('MetaCons "MethodTypeParameterDeclaration" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 TypeParameterTarget)) :+: (C1 ('MetaCons "MethodBoundTypeParameterDeclaration" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 TypeParameterBoundTarget)) :+: C1 ('MetaCons "MethodReturnType" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "MethodReceiverType" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "MethodFormalParameter" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 FormalParameterTarget)) :+: C1 ('MetaCons "MethodThrowsClause" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ThrowsTarget)))))
type Rep (ClassTypeAnnotation High) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

type Rep (ClassTypeAnnotation High) = D1 ('MetaData "ClassTypeAnnotation" "Language.JVM.Attribute.Annotations" "jvm-binary-0.10.0-6UZh5809b0fJPIjalFrBq2" 'False) (C1 ('MetaCons "ClassTypeParameterDeclaration" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 TypeParameterTarget)) :+: (C1 ('MetaCons "ClassSuperType" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 SupertypeTarget)) :+: C1 ('MetaCons "ClassBoundTypeParameterDeclaration" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 TypeParameterBoundTarget))))
type Rep (EnumValue High) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

type Rep (EnumValue High) = D1 ('MetaData "EnumValue" "Language.JVM.Attribute.Annotations" "jvm-binary-0.10.0-6UZh5809b0fJPIjalFrBq2" 'False) (C1 ('MetaCons "EnumValue" 'PrefixI 'True) (S1 ('MetaSel ('Just "enumTypeName") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Ref FieldDescriptor High)) :*: S1 ('MetaSel ('Just "enunConstName") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Ref Text High))))
type Rep (ElementValue High) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

type Rep (ElementValue High) = D1 ('MetaData "ElementValue" "Language.JVM.Attribute.Annotations" "jvm-binary-0.10.0-6UZh5809b0fJPIjalFrBq2" 'False) (((C1 ('MetaCons "EByte" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Ref VInteger High))) :+: (C1 ('MetaCons "EChar" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Ref VInteger High))) :+: C1 ('MetaCons "EDouble" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Ref VDouble High))))) :+: (C1 ('MetaCons "EFloat" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Ref VFloat High))) :+: (C1 ('MetaCons "EInt" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Ref VInteger High))) :+: C1 ('MetaCons "ELong" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Ref VLong High)))))) :+: ((C1 ('MetaCons "EShort" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Ref VInteger High))) :+: (C1 ('MetaCons "EBoolean" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Ref VInteger High))) :+: C1 ('MetaCons "EString" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Ref VString High))))) :+: ((C1 ('MetaCons "EEnum" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (EnumValue High))) :+: C1 ('MetaCons "EClass" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Ref ReturnDescriptor High)))) :+: (C1 ('MetaCons "EAnnotationType" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Annotation High))) :+: C1 ('MetaCons "EArrayType" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (SizedList16 (ElementValue High))))))))
type Rep (ValuePair High) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

type Rep (ValuePair High) = D1 ('MetaData "ValuePair" "Language.JVM.Attribute.Annotations" "jvm-binary-0.10.0-6UZh5809b0fJPIjalFrBq2" 'False) (C1 ('MetaCons "ValuePair" 'PrefixI 'True) (S1 ('MetaSel ('Just "name") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Ref Text High)) :*: S1 ('MetaSel ('Just "value") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (ElementValue High))))
type Rep (Annotation High) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

type Rep (Annotation High) = D1 ('MetaData "Annotation" "Language.JVM.Attribute.Annotations" "jvm-binary-0.10.0-6UZh5809b0fJPIjalFrBq2" 'False) (C1 ('MetaCons "Annotation" 'PrefixI 'True) (S1 ('MetaSel ('Just "annotationType") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Ref FieldDescriptor High)) :*: S1 ('MetaSel ('Just "annotationValuePairs") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (SizedList16 (ValuePair High)))))
type Rep (RuntimeInvisibleParameterAnnotations High) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

type Rep (RuntimeInvisibleParameterAnnotations High) = D1 ('MetaData "RuntimeInvisibleParameterAnnotations" "Language.JVM.Attribute.Annotations" "jvm-binary-0.10.0-6UZh5809b0fJPIjalFrBq2" 'True) (C1 ('MetaCons "RuntimeInvisibleParameterAnnotations" 'PrefixI 'True) (S1 ('MetaSel ('Just "asListOfInvisibleParameterAnnotations") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SizedList8 (SizedList16 (Annotation High))))))
type Rep (RuntimeVisibleParameterAnnotations High) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

type Rep (RuntimeVisibleParameterAnnotations High) = D1 ('MetaData "RuntimeVisibleParameterAnnotations" "Language.JVM.Attribute.Annotations" "jvm-binary-0.10.0-6UZh5809b0fJPIjalFrBq2" 'True) (C1 ('MetaCons "RuntimeVisibleParameterAnnotations" 'PrefixI 'True) (S1 ('MetaSel ('Just "asListOfVisibleParameterAnnotations") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SizedList8 (SizedList16 (Annotation High))))))
type Rep (RuntimeInvisibleAnnotations High) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

type Rep (RuntimeInvisibleAnnotations High) = D1 ('MetaData "RuntimeInvisibleAnnotations" "Language.JVM.Attribute.Annotations" "jvm-binary-0.10.0-6UZh5809b0fJPIjalFrBq2" 'True) (C1 ('MetaCons "RuntimeInvisibleAnnotations" 'PrefixI 'True) (S1 ('MetaSel ('Just "asListOfRuntimeInvisibleAnnotations") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SizedList16 (Annotation High)))))
type Rep (RuntimeVisibleAnnotations High) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

type Rep (RuntimeVisibleAnnotations High) = D1 ('MetaData "RuntimeVisibleAnnotations" "Language.JVM.Attribute.Annotations" "jvm-binary-0.10.0-6UZh5809b0fJPIjalFrBq2" 'True) (C1 ('MetaCons "RuntimeVisibleAnnotations" 'PrefixI 'True) (S1 ('MetaSel ('Just "asListOfRuntimeVisibleAnnotations") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SizedList16 (Annotation High)))))
type Rep (CodeAttributes High) Source # 
Instance details

Defined in Language.JVM.Attribute.Code

type Rep (ExceptionTable High) Source # 
Instance details

Defined in Language.JVM.Attribute.Code

type Rep (ExceptionTable High) = D1 ('MetaData "ExceptionTable" "Language.JVM.Attribute.Code" "jvm-binary-0.10.0-6UZh5809b0fJPIjalFrBq2" 'False) (C1 ('MetaCons "ExceptionTable" 'PrefixI 'True) ((S1 ('MetaSel ('Just "start") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (ByteCodeRef High)) :*: S1 ('MetaSel ('Just "end") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (ByteCodeRef High))) :*: (S1 ('MetaSel ('Just "handler") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (ByteCodeRef High)) :*: S1 ('MetaSel ('Just "catchType") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Ref (Maybe ClassName) High)))))
type Rep (Code High) Source # 
Instance details

Defined in Language.JVM.Attribute.Code

type Rep (Code High) = D1 ('MetaData "Code" "Language.JVM.Attribute.Code" "jvm-binary-0.10.0-6UZh5809b0fJPIjalFrBq2" 'False) (C1 ('MetaCons "Code" 'PrefixI 'True) ((S1 ('MetaSel ('Just "codeMaxStack") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Word16) :*: S1 ('MetaSel ('Just "codeMaxLocals") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Word16)) :*: (S1 ('MetaSel ('Just "codeByteCode") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (ByteCode High)) :*: (S1 ('MetaSel ('Just "codeExceptionTable") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (SizedList16 (ExceptionTable High))) :*: S1 ('MetaSel ('Just "codeAttributes") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Attributes CodeAttributes High))))))
type Rep (MethodParameter High) Source # 
Instance details

Defined in Language.JVM.Attribute.MethodParameters

type Rep (MethodParameter High) = D1 ('MetaData "MethodParameter" "Language.JVM.Attribute.MethodParameters" "jvm-binary-0.10.0-6UZh5809b0fJPIjalFrBq2" 'False) (C1 ('MetaCons "MethodParameter" 'PrefixI 'True) (S1 ('MetaSel ('Just "parameterName") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Ref Text High)) :*: S1 ('MetaSel ('Just "parameterAccessFlags") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (BitSet16 PAccessFlag))))
type Rep (MethodParameters High) Source # 
Instance details

Defined in Language.JVM.Attribute.MethodParameters

type Rep (MethodParameters High) = D1 ('MetaData "MethodParameters" "Language.JVM.Attribute.MethodParameters" "jvm-binary-0.10.0-6UZh5809b0fJPIjalFrBq2" 'True) (C1 ('MetaCons "MethodParameters" 'PrefixI 'True) (S1 ('MetaSel ('Just "methodParameters") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SizedList8 (MethodParameter High)))))
type Rep (MethodAttributes High) Source # 
Instance details

Defined in Language.JVM.Method

type Rep (MethodAttributes High) = D1 ('MetaData "MethodAttributes" "Language.JVM.Method" "jvm-binary-0.10.0-6UZh5809b0fJPIjalFrBq2" 'False) (C1 ('MetaCons "MethodAttributes" 'PrefixI 'True) (((S1 ('MetaSel ('Just "maCode") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Code High]) :*: (S1 ('MetaSel ('Just "maExceptions") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Exceptions High]) :*: S1 ('MetaSel ('Just "maSignatures") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Signature High]))) :*: (S1 ('MetaSel ('Just "maAnnotationDefault") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [AnnotationDefault High]) :*: (S1 ('MetaSel ('Just "maMethodParameters") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [MethodParameters High]) :*: S1 ('MetaSel ('Just "maVisibleAnnotations") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [RuntimeVisibleAnnotations High])))) :*: ((S1 ('MetaSel ('Just "maInvisibleAnnotations") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [RuntimeInvisibleAnnotations High]) :*: (S1 ('MetaSel ('Just "maVisibleParameterAnnotations") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [RuntimeVisibleParameterAnnotations High]) :*: S1 ('MetaSel ('Just "maInvisibleParameterAnnotations") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [RuntimeInvisibleParameterAnnotations High]))) :*: (S1 ('MetaSel ('Just "maVisibleTypeAnnotations") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [RuntimeVisibleTypeAnnotations MethodTypeAnnotation High]) :*: (S1 ('MetaSel ('Just "maInvisibleTypeAnnotations") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [RuntimeInvisibleTypeAnnotations MethodTypeAnnotation High]) :*: S1 ('MetaSel ('Just "maOthers") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Attribute High]))))))
type Rep (Method High) Source # 
Instance details

Defined in Language.JVM.Method

type Rep (Method High) = D1 ('MetaData "Method" "Language.JVM.Method" "jvm-binary-0.10.0-6UZh5809b0fJPIjalFrBq2" 'False) (C1 ('MetaCons "Method" 'PrefixI 'True) ((S1 ('MetaSel ('Just "mAccessFlags'") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (BitSet16 MAccessFlag)) :*: S1 ('MetaSel ('Just "mName") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Ref Text High))) :*: (S1 ('MetaSel ('Just "mDescriptor") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Ref MethodDescriptor High)) :*: S1 ('MetaSel ('Just "mAttributes") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Attributes MethodAttributes High)))))
type Rep (FieldAttributes High) Source # 
Instance details

Defined in Language.JVM.Field

type Rep (Field High) Source # 
Instance details

Defined in Language.JVM.Field

type Rep (Field High) = D1 ('MetaData "Field" "Language.JVM.Field" "jvm-binary-0.10.0-6UZh5809b0fJPIjalFrBq2" 'False) (C1 ('MetaCons "Field" 'PrefixI 'True) ((S1 ('MetaSel ('Just "fAccessFlags'") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (BitSet16 FAccessFlag)) :*: S1 ('MetaSel ('Just "fName") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Ref Text High))) :*: (S1 ('MetaSel ('Just "fDescriptor") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Ref FieldDescriptor High)) :*: S1 ('MetaSel ('Just "fAttributes") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Attributes FieldAttributes High)))))
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.10.0-6UZh5809b0fJPIjalFrBq2" '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.10.0-6UZh5809b0fJPIjalFrBq2" '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 (ClassFile High) = D1 ('MetaData "ClassFile" "Language.JVM.ClassFile" "jvm-binary-0.10.0-6UZh5809b0fJPIjalFrBq2" 'False) (C1 ('MetaCons "ClassFile" 'PrefixI 'True) (((S1 ('MetaSel ('Just "cMagicNumber") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Word32) :*: S1 ('MetaSel ('Just "cMinorVersion") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Word16)) :*: (S1 ('MetaSel ('Just "cMajorVersion") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Word16) :*: (S1 ('MetaSel ('Just "cConstantPool") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Choice (ConstantPool High) () High)) :*: S1 ('MetaSel ('Just "cAccessFlags'") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (BitSet16 CAccessFlag))))) :*: ((S1 ('MetaSel ('Just "cThisClass") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Ref ClassName High)) :*: (S1 ('MetaSel ('Just "cSuperClass") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Ref ClassName High)) :*: S1 ('MetaSel ('Just "cInterfaces") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (SizedList16 (Ref ClassName High))))) :*: (S1 ('MetaSel ('Just "cFields'") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (SizedList16 (Field High))) :*: (S1 ('MetaSel ('Just "cMethods'") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (SizedList16 (Method High))) :*: S1 ('MetaSel ('Just "cAttributes") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Attributes ClassAttributes High)))))))
type Rep (RuntimeInvisibleTypeAnnotations m High) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

type Rep (RuntimeInvisibleTypeAnnotations m High) = D1 ('MetaData "RuntimeInvisibleTypeAnnotations" "Language.JVM.Attribute.Annotations" "jvm-binary-0.10.0-6UZh5809b0fJPIjalFrBq2" 'True) (C1 ('MetaCons "RuntimeInvisibleTypeAnnotations" 'PrefixI 'True) (S1 ('MetaSel ('Just "asListOfInvisibleTypeAnnotations") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SizedList16 (TypeAnnotation m High)))))
type Rep (RuntimeVisibleTypeAnnotations m High) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

type Rep (RuntimeVisibleTypeAnnotations m High) = D1 ('MetaData "RuntimeVisibleTypeAnnotations" "Language.JVM.Attribute.Annotations" "jvm-binary-0.10.0-6UZh5809b0fJPIjalFrBq2" 'True) (C1 ('MetaCons "RuntimeVisibleTypeAnnotations" 'PrefixI 'True) (S1 ('MetaSel ('Just "asListOfVisibleTypeAnnotations") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SizedList16 (TypeAnnotation m High)))))
type Rep (TypeAnnotation m High) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

type Rep (TypeAnnotation m High) = D1 ('MetaData "TypeAnnotation" "Language.JVM.Attribute.Annotations" "jvm-binary-0.10.0-6UZh5809b0fJPIjalFrBq2" 'False) (C1 ('MetaCons "TypeAnnotation" 'PrefixI 'True) ((S1 ('MetaSel ('Just "typeAnnotationTarget") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (m High)) :*: S1 ('MetaSel ('Just "typeAnnotationPath") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 TypePath)) :*: (S1 ('MetaSel ('Just "typeAnnotationType") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Ref FieldDescriptor High)) :*: S1 ('MetaSel ('Just "typeAnnotationValuePairs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SizedList16 (ValuePair High))))))

data Low Source #

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

Instances

Instances details
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 (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 (BootstrapMethod Low) Source # 
Instance details

Defined in Language.JVM.Attribute.BootstrapMethods

Eq (BootstrapMethods Low) Source # 
Instance details

Defined in Language.JVM.Attribute.BootstrapMethods

Eq (AnnotationDefault Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Eq (TypeArgumentTarget Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Eq (LocalvarEntry Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Eq (CodeTypeAnnotation Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Eq (FieldTypeAnnotation Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Eq (MethodTypeAnnotation Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Eq (ClassTypeAnnotation Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Eq (EnumValue Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Eq (ElementValue Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Eq (ValuePair Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Eq (Annotation Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Eq (RuntimeInvisibleParameterAnnotations Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Eq (RuntimeVisibleParameterAnnotations Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Eq (RuntimeInvisibleAnnotations Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Eq (RuntimeVisibleAnnotations Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

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 (MethodParameter Low) Source # 
Instance details

Defined in Language.JVM.Attribute.MethodParameters

Eq (MethodParameters Low) Source # 
Instance details

Defined in Language.JVM.Attribute.MethodParameters

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 (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 (BootstrapMethod Low) Source # 
Instance details

Defined in Language.JVM.Attribute.BootstrapMethods

Ord (BootstrapMethods Low) Source # 
Instance details

Defined in Language.JVM.Attribute.BootstrapMethods

Ord (AnnotationDefault Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Ord (TypeArgumentTarget Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Ord (LocalvarEntry Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Ord (CodeTypeAnnotation Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Ord (FieldTypeAnnotation Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Ord (MethodTypeAnnotation Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Ord (ClassTypeAnnotation Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Ord (EnumValue Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Ord (ElementValue Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Ord (ValuePair Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Ord (Annotation Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Ord (RuntimeInvisibleParameterAnnotations Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Ord (RuntimeVisibleParameterAnnotations Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Ord (RuntimeInvisibleAnnotations Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Ord (RuntimeVisibleAnnotations Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

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 (MethodParameter Low) Source # 
Instance details

Defined in Language.JVM.Attribute.MethodParameters

Ord (MethodParameters Low) Source # 
Instance details

Defined in Language.JVM.Attribute.MethodParameters

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 (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 (BootstrapMethod Low) Source # 
Instance details

Defined in Language.JVM.Attribute.BootstrapMethods

Show (BootstrapMethods Low) Source # 
Instance details

Defined in Language.JVM.Attribute.BootstrapMethods

Show (AnnotationDefault Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Show (TypeArgumentTarget Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Show (LocalvarEntry Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Show (CodeTypeAnnotation Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Show (FieldTypeAnnotation Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Show (MethodTypeAnnotation Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Show (ClassTypeAnnotation Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Show (EnumValue Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Show (ElementValue Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Show (ValuePair Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Show (Annotation Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Show (RuntimeInvisibleParameterAnnotations Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Show (RuntimeVisibleParameterAnnotations Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Show (RuntimeInvisibleAnnotations Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Show (RuntimeVisibleAnnotations Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

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 (MethodParameter Low) Source # 
Instance details

Defined in Language.JVM.Attribute.MethodParameters

Show (MethodParameters Low) Source # 
Instance details

Defined in Language.JVM.Attribute.MethodParameters

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 (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 (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 (AnnotationDefault Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Associated Types

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

Generic (TypeArgumentTarget Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Associated Types

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

Generic (LocalvarEntry Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Associated Types

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

Generic (CodeTypeAnnotation Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Associated Types

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

Generic (FieldTypeAnnotation Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Associated Types

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

Generic (MethodTypeAnnotation Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Associated Types

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

Generic (ClassTypeAnnotation Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Associated Types

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

Generic (EnumValue Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Associated Types

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

Generic (ElementValue Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Associated Types

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

Generic (ValuePair Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Associated Types

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

Generic (Annotation Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Associated Types

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

Generic (RuntimeInvisibleParameterAnnotations Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Associated Types

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

Generic (RuntimeVisibleParameterAnnotations Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Associated Types

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

Generic (RuntimeInvisibleAnnotations Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Associated Types

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

Generic (RuntimeVisibleAnnotations Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Associated Types

type Rep (RuntimeVisibleAnnotations 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 (MethodParameter Low) Source # 
Instance details

Defined in Language.JVM.Attribute.MethodParameters

Associated Types

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

Generic (MethodParameters Low) Source # 
Instance details

Defined in Language.JVM.Attribute.MethodParameters

Associated Types

type Rep (MethodParameters 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 (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 (BootstrapMethod Low) Source # 
Instance details

Defined in Language.JVM.Attribute.BootstrapMethods

Binary (BootstrapMethods Low) Source # 
Instance details

Defined in Language.JVM.Attribute.BootstrapMethods

Binary (AnnotationDefault Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Binary (TypeArgumentTarget Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Binary (LocalvarEntry Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Binary (CodeTypeAnnotation Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Binary (FieldTypeAnnotation Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Binary (MethodTypeAnnotation Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Binary (ClassTypeAnnotation Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Binary (EnumValue Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Binary (ElementValue Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Binary (ValuePair Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Binary (Annotation Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Binary (RuntimeInvisibleParameterAnnotations Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Binary (RuntimeVisibleParameterAnnotations Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Binary (RuntimeInvisibleAnnotations Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Binary (RuntimeVisibleAnnotations Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

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 (MethodParameter Low) Source # 
Instance details

Defined in Language.JVM.Attribute.MethodParameters

Binary (MethodParameters Low) Source # 
Instance details

Defined in Language.JVM.Attribute.MethodParameters

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 (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 (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 (AnnotationDefault Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Methods

rnf :: AnnotationDefault Low -> () #

NFData (TypeArgumentTarget Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Methods

rnf :: TypeArgumentTarget Low -> () #

NFData (LocalvarEntry Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Methods

rnf :: LocalvarEntry Low -> () #

NFData (CodeTypeAnnotation Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Methods

rnf :: CodeTypeAnnotation Low -> () #

NFData (FieldTypeAnnotation Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Methods

rnf :: FieldTypeAnnotation Low -> () #

NFData (MethodTypeAnnotation Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Methods

rnf :: MethodTypeAnnotation Low -> () #

NFData (ClassTypeAnnotation Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Methods

rnf :: ClassTypeAnnotation Low -> () #

NFData (EnumValue Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Methods

rnf :: EnumValue Low -> () #

NFData (ElementValue Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Methods

rnf :: ElementValue Low -> () #

NFData (ValuePair Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Methods

rnf :: ValuePair Low -> () #

NFData (Annotation Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Methods

rnf :: Annotation Low -> () #

NFData (RuntimeInvisibleParameterAnnotations Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

NFData (RuntimeVisibleParameterAnnotations Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

NFData (RuntimeInvisibleAnnotations Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

NFData (RuntimeVisibleAnnotations Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

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 (MethodParameter Low) Source # 
Instance details

Defined in Language.JVM.Attribute.MethodParameters

Methods

rnf :: MethodParameter Low -> () #

NFData (MethodParameters Low) Source # 
Instance details

Defined in Language.JVM.Attribute.MethodParameters

Methods

rnf :: MethodParameters 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 (BootstrapMethods Low) Source #

BootstrapMethods is an Attribute.

Instance details

Defined in Language.JVM.Attribute.BootstrapMethods

IsAttribute (AnnotationDefault Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

IsAttribute (RuntimeInvisibleParameterAnnotations Low) Source #

RuntimeInvisibleParameterAnnotations is an Attribute.

Instance details

Defined in Language.JVM.Attribute.Annotations

IsAttribute (RuntimeVisibleParameterAnnotations Low) Source #

RuntimeVisibleParameterAnnotations is an Attribute.

Instance details

Defined in Language.JVM.Attribute.Annotations

IsAttribute (RuntimeInvisibleAnnotations Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

IsAttribute (RuntimeVisibleAnnotations Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

IsAttribute (Code Low) Source #

Code is an Attribute.

Instance details

Defined in Language.JVM.Attribute.Code

IsAttribute (MethodParameters Low) Source #

BootstrapMethods is an Attribute.

Instance details

Defined in Language.JVM.Attribute.MethodParameters

IsAttribute (InnerClasses Low) Source #

InnerClasses is an Attribute.

Instance details

Defined in Language.JVM.Attribute.InnerClasses

Eq (m Low) => Eq (RuntimeInvisibleTypeAnnotations m Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Eq (m Low) => Eq (RuntimeVisibleTypeAnnotations m Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Eq (m Low) => Eq (TypeAnnotation m Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Ord (m Low) => Ord (RuntimeInvisibleTypeAnnotations m Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Ord (m Low) => Ord (RuntimeVisibleTypeAnnotations m Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Ord (m Low) => Ord (TypeAnnotation m Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Show (m Low) => Show (RuntimeInvisibleTypeAnnotations m Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Show (m Low) => Show (RuntimeVisibleTypeAnnotations m Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Show (m Low) => Show (TypeAnnotation m Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Generic (m Low) => Generic (RuntimeInvisibleTypeAnnotations m Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Associated Types

type Rep (RuntimeInvisibleTypeAnnotations m Low) :: Type -> Type #

Generic (m Low) => Generic (RuntimeVisibleTypeAnnotations m Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Associated Types

type Rep (RuntimeVisibleTypeAnnotations m Low) :: Type -> Type #

Generic (m Low) => Generic (TypeAnnotation m Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Associated Types

type Rep (TypeAnnotation m Low) :: Type -> Type #

(Generic (m Low), Binary (m Low)) => Binary (RuntimeInvisibleTypeAnnotations m Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

(Generic (m Low), Binary (m Low)) => Binary (RuntimeVisibleTypeAnnotations m Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Binary (m Low) => Binary (TypeAnnotation m Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

(Generic (m Low), NFData (m Low)) => NFData (RuntimeInvisibleTypeAnnotations m Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

(Generic (m Low), NFData (m Low)) => NFData (RuntimeVisibleTypeAnnotations m Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

(Generic (m Low), NFData (m Low)) => NFData (TypeAnnotation m Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Methods

rnf :: TypeAnnotation m Low -> () #

(Generic (m Low), Binary (m Low)) => IsAttribute (RuntimeInvisibleTypeAnnotations m Low) Source #

RuntimeInvisibleTypeAnnotations is an Attribute.

Instance details

Defined in Language.JVM.Attribute.Annotations

(Generic (m Low), Binary (m Low)) => IsAttribute (RuntimeVisibleTypeAnnotations m Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

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.10.0-6UZh5809b0fJPIjalFrBq2" '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.10.0-6UZh5809b0fJPIjalFrBq2" 'True) (C1 ('MetaCons "MethodHandleInterface" 'PrefixI 'True) (S1 ('MetaSel ('Just "methodHandleInterfaceRef") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Ref 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.10.0-6UZh5809b0fJPIjalFrBq2" 'False) (C1 ('MetaCons "MethodHandleField" 'PrefixI 'True) (S1 ('MetaSel ('Just "methodHandleFieldKind") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 MethodHandleFieldKind) :*: S1 ('MetaSel ('Just "methodHandleFieldRef") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Ref AbsFieldId Low))))
type Rep (MethodHandle Low) Source # 
Instance details

Defined in Language.JVM.Constant

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.10.0-6UZh5809b0fJPIjalFrBq2" '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 (Choice (Index, Index) AbsFieldId Low))) :+: (C1 ('MetaCons "CMethodRef" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Choice (Index, Index) (InRefType MethodId) Low))) :+: C1 ('MetaCons "CInterfaceMethodRef" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Choice (Index, Index) (InRefType 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.10.0-6UZh5809b0fJPIjalFrBq2" '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 (ByteCodeOpr Low) = D1 ('MetaData "ByteCodeOpr" "Language.JVM.ByteCode" "jvm-binary-0.10.0-6UZh5809b0fJPIjalFrBq2" 'False) (((((C1 ('MetaCons "ArrayLoad" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ArrayType)) :+: C1 ('MetaCons "ArrayStore" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ArrayType))) :+: (C1 ('MetaCons "Push" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (BConstant Low))) :+: C1 ('MetaCons "Load" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 LocalType) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 LocalAddress)))) :+: ((C1 ('MetaCons "Store" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 LocalType) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 LocalAddress)) :+: C1 ('MetaCons "BinaryOpr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 BinOpr) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ArithmeticType))) :+: (C1 ('MetaCons "Neg" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ArithmeticType)) :+: (C1 ('MetaCons "BitOpr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 BitOpr) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 WordSize)) :+: C1 ('MetaCons "IncrLocal" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 LocalAddress) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 IncrementAmount)))))) :+: (((C1 ('MetaCons "Cast" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 CastOpr)) :+: C1 ('MetaCons "CompareLongs" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "CompareFloating" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bool) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 WordSize)) :+: C1 ('MetaCons "If" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 CmpOpr) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 OneOrTwo) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (ShortRelativeRef Low)))))) :+: ((C1 ('MetaCons "IfRef" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bool) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 OneOrTwo) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (ShortRelativeRef Low)))) :+: C1 ('MetaCons "Goto" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (LongRelativeRef Low)))) :+: (C1 ('MetaCons "Jsr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (LongRelativeRef Low))) :+: (C1 ('MetaCons "Ret" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 LocalAddress)) :+: C1 ('MetaCons "TableSwitch" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (LongRelativeRef Low)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (SwitchTable Low)))))))) :+: ((((C1 ('MetaCons "LookupSwitch" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (LongRelativeRef Low)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Vector (Int32, LongRelativeRef Low)))) :+: C1 ('MetaCons "Get" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 FieldAccess) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Ref AbsFieldId Low)))) :+: (C1 ('MetaCons "Put" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 FieldAccess) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Ref AbsFieldId Low))) :+: C1 ('MetaCons "Invoke" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Invocation Low))))) :+: ((C1 ('MetaCons "New" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Ref ClassName Low))) :+: C1 ('MetaCons "NewArray" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Choice LowNewArrayType NewArrayType Low)))) :+: (C1 ('MetaCons "ArrayLength" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Throw" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CheckCast" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Ref JRefType Low))))))) :+: (((C1 ('MetaCons "InstanceOf" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Ref JRefType Low))) :+: C1 ('MetaCons "Monitor" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bool))) :+: (C1 ('MetaCons "Return" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe LocalType))) :+: C1 ('MetaCons "Nop" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "Pop" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 WordSize)) :+: C1 ('MetaCons "Dup" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 WordSize))) :+: (C1 ('MetaCons "DupX1" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 WordSize)) :+: (C1 ('MetaCons "DupX2" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 WordSize)) :+: C1 ('MetaCons "Swap" 'PrefixI 'False) (U1 :: Type -> Type)))))))
type Rep (SwitchTable Low) Source # 
Instance details

Defined in Language.JVM.ByteCode

type Rep (SwitchTable Low) = D1 ('MetaData "SwitchTable" "Language.JVM.ByteCode" "jvm-binary-0.10.0-6UZh5809b0fJPIjalFrBq2" 'False) (C1 ('MetaCons "SwitchTable" 'PrefixI 'True) (S1 ('MetaSel ('Just "switchLow") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Int32) :*: S1 ('MetaSel ('Just "switchOffsets") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Vector (LongRelativeRef Low)))))
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.10.0-6UZh5809b0fJPIjalFrBq2" '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.10.0-6UZh5809b0fJPIjalFrBq2" '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.10.0-6UZh5809b0fJPIjalFrBq2" '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.10.0-6UZh5809b0fJPIjalFrBq2" '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.10.0-6UZh5809b0fJPIjalFrBq2" '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 'SourceStrict 'DecidedStrict) (Rec0 (Ref JRefType Low))) :+: C1 ('MetaCons "VTUninitialized" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (ByteCodeRef Low)))))))
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.10.0-6UZh5809b0fJPIjalFrBq2" '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.10.0-6UZh5809b0fJPIjalFrBq2" '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.10.0-6UZh5809b0fJPIjalFrBq2" '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.10.0-6UZh5809b0fJPIjalFrBq2" '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.10.0-6UZh5809b0fJPIjalFrBq2" '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.10.0-6UZh5809b0fJPIjalFrBq2" 'True) (C1 ('MetaCons "ConstantValue" 'PrefixI 'True) (S1 ('MetaSel ('Just "constantValue") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Ref JValue Low))))
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.10.0-6UZh5809b0fJPIjalFrBq2" '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.10.0-6UZh5809b0fJPIjalFrBq2" 'True) (C1 ('MetaCons "BootstrapMethods" 'PrefixI 'True) (S1 ('MetaSel ('Just "methods'") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SizedList16 (BootstrapMethod Low)))))
type Rep (AnnotationDefault Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

type Rep (AnnotationDefault Low) = D1 ('MetaData "AnnotationDefault" "Language.JVM.Attribute.Annotations" "jvm-binary-0.10.0-6UZh5809b0fJPIjalFrBq2" 'True) (C1 ('MetaCons "AnnotationDefault" 'PrefixI 'True) (S1 ('MetaSel ('Just "defaultValue") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (ElementValue Low))))
type Rep (TypeArgumentTarget Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

type Rep (TypeArgumentTarget Low) = D1 ('MetaData "TypeArgumentTarget" "Language.JVM.Attribute.Annotations" "jvm-binary-0.10.0-6UZh5809b0fJPIjalFrBq2" 'False) (C1 ('MetaCons "TypeArgumentTarget" 'PrefixI 'True) (S1 ('MetaSel ('Just "typeArgumentOffset") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (ByteCodeRef Low)) :*: S1 ('MetaSel ('Just "typeArgumentIndex") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word8)))
type Rep (LocalvarEntry Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

type Rep (LocalvarEntry Low) = D1 ('MetaData "LocalvarEntry" "Language.JVM.Attribute.Annotations" "jvm-binary-0.10.0-6UZh5809b0fJPIjalFrBq2" 'False) (C1 ('MetaCons "LocalvarEntry" 'PrefixI 'True) (S1 ('MetaSel ('Just "lvStartPc") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (ByteCodeRef Low)) :*: (S1 ('MetaSel ('Just "lvLength") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Word16) :*: S1 ('MetaSel ('Just "lvLocalVarIndex") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Word16))))
type Rep (CodeTypeAnnotation Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

type Rep (CodeTypeAnnotation Low) = D1 ('MetaData "CodeTypeAnnotation" "Language.JVM.Attribute.Annotations" "jvm-binary-0.10.0-6UZh5809b0fJPIjalFrBq2" 'False) (((C1 ('MetaCons "LocalVariableDeclaration" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (LocalvarTarget Low))) :+: (C1 ('MetaCons "ResourceVariableDeclaration" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (LocalvarTarget Low))) :+: C1 ('MetaCons "ExceptionParameterDeclaration" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 CatchTarget)))) :+: (C1 ('MetaCons "InstanceOfExpression" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (OffsetTarget Low))) :+: (C1 ('MetaCons "NewExpression" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (OffsetTarget Low))) :+: C1 ('MetaCons "NewMethodReferenceExpression" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (OffsetTarget Low)))))) :+: ((C1 ('MetaCons "IdentifierMethodReferenceExpression" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (OffsetTarget Low))) :+: (C1 ('MetaCons "CastExpression" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (TypeArgumentTarget Low))) :+: C1 ('MetaCons "ConstructorExpression" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (TypeArgumentTarget Low))))) :+: (C1 ('MetaCons "MethodIncovationExpression" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (TypeArgumentTarget Low))) :+: (C1 ('MetaCons "GenericNewMethodReferenceExpression" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (TypeArgumentTarget Low))) :+: C1 ('MetaCons "GenericIdentifierwMethodReferenceExpression" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (TypeArgumentTarget Low)))))))
type Rep (FieldTypeAnnotation Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

type Rep (FieldTypeAnnotation Low) = D1 ('MetaData "FieldTypeAnnotation" "Language.JVM.Attribute.Annotations" "jvm-binary-0.10.0-6UZh5809b0fJPIjalFrBq2" 'False) (C1 ('MetaCons "FieldTypeAnnotation" 'PrefixI 'False) (U1 :: Type -> Type))
type Rep (MethodTypeAnnotation Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

type Rep (MethodTypeAnnotation Low) = D1 ('MetaData "MethodTypeAnnotation" "Language.JVM.Attribute.Annotations" "jvm-binary-0.10.0-6UZh5809b0fJPIjalFrBq2" 'False) ((C1 ('MetaCons "MethodTypeParameterDeclaration" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 TypeParameterTarget)) :+: (C1 ('MetaCons "MethodBoundTypeParameterDeclaration" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 TypeParameterBoundTarget)) :+: C1 ('MetaCons "MethodReturnType" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "MethodReceiverType" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "MethodFormalParameter" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 FormalParameterTarget)) :+: C1 ('MetaCons "MethodThrowsClause" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ThrowsTarget)))))
type Rep (ClassTypeAnnotation Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

type Rep (ClassTypeAnnotation Low) = D1 ('MetaData "ClassTypeAnnotation" "Language.JVM.Attribute.Annotations" "jvm-binary-0.10.0-6UZh5809b0fJPIjalFrBq2" 'False) (C1 ('MetaCons "ClassTypeParameterDeclaration" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 TypeParameterTarget)) :+: (C1 ('MetaCons "ClassSuperType" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 SupertypeTarget)) :+: C1 ('MetaCons "ClassBoundTypeParameterDeclaration" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 TypeParameterBoundTarget))))
type Rep (EnumValue Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

type Rep (EnumValue Low) = D1 ('MetaData "EnumValue" "Language.JVM.Attribute.Annotations" "jvm-binary-0.10.0-6UZh5809b0fJPIjalFrBq2" 'False) (C1 ('MetaCons "EnumValue" 'PrefixI 'True) (S1 ('MetaSel ('Just "enumTypeName") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Ref FieldDescriptor Low)) :*: S1 ('MetaSel ('Just "enunConstName") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Ref Text Low))))
type Rep (ElementValue Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

type Rep (ElementValue Low) = D1 ('MetaData "ElementValue" "Language.JVM.Attribute.Annotations" "jvm-binary-0.10.0-6UZh5809b0fJPIjalFrBq2" 'False) (((C1 ('MetaCons "EByte" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Ref VInteger Low))) :+: (C1 ('MetaCons "EChar" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Ref VInteger Low))) :+: C1 ('MetaCons "EDouble" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Ref VDouble Low))))) :+: (C1 ('MetaCons "EFloat" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Ref VFloat Low))) :+: (C1 ('MetaCons "EInt" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Ref VInteger Low))) :+: C1 ('MetaCons "ELong" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Ref VLong Low)))))) :+: ((C1 ('MetaCons "EShort" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Ref VInteger Low))) :+: (C1 ('MetaCons "EBoolean" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Ref VInteger Low))) :+: C1 ('MetaCons "EString" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Ref VString Low))))) :+: ((C1 ('MetaCons "EEnum" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (EnumValue Low))) :+: C1 ('MetaCons "EClass" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Ref ReturnDescriptor Low)))) :+: (C1 ('MetaCons "EAnnotationType" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Annotation Low))) :+: C1 ('MetaCons "EArrayType" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (SizedList16 (ElementValue Low))))))))
type Rep (ValuePair Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

type Rep (ValuePair Low) = D1 ('MetaData "ValuePair" "Language.JVM.Attribute.Annotations" "jvm-binary-0.10.0-6UZh5809b0fJPIjalFrBq2" 'False) (C1 ('MetaCons "ValuePair" 'PrefixI 'True) (S1 ('MetaSel ('Just "name") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Ref Text Low)) :*: S1 ('MetaSel ('Just "value") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (ElementValue Low))))
type Rep (Annotation Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

type Rep (Annotation Low) = D1 ('MetaData "Annotation" "Language.JVM.Attribute.Annotations" "jvm-binary-0.10.0-6UZh5809b0fJPIjalFrBq2" 'False) (C1 ('MetaCons "Annotation" 'PrefixI 'True) (S1 ('MetaSel ('Just "annotationType") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Ref FieldDescriptor Low)) :*: S1 ('MetaSel ('Just "annotationValuePairs") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (SizedList16 (ValuePair Low)))))
type Rep (RuntimeInvisibleParameterAnnotations Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

type Rep (RuntimeInvisibleParameterAnnotations Low) = D1 ('MetaData "RuntimeInvisibleParameterAnnotations" "Language.JVM.Attribute.Annotations" "jvm-binary-0.10.0-6UZh5809b0fJPIjalFrBq2" 'True) (C1 ('MetaCons "RuntimeInvisibleParameterAnnotations" 'PrefixI 'True) (S1 ('MetaSel ('Just "asListOfInvisibleParameterAnnotations") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SizedList8 (SizedList16 (Annotation Low))))))
type Rep (RuntimeVisibleParameterAnnotations Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

type Rep (RuntimeVisibleParameterAnnotations Low) = D1 ('MetaData "RuntimeVisibleParameterAnnotations" "Language.JVM.Attribute.Annotations" "jvm-binary-0.10.0-6UZh5809b0fJPIjalFrBq2" 'True) (C1 ('MetaCons "RuntimeVisibleParameterAnnotations" 'PrefixI 'True) (S1 ('MetaSel ('Just "asListOfVisibleParameterAnnotations") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SizedList8 (SizedList16 (Annotation Low))))))
type Rep (RuntimeInvisibleAnnotations Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

type Rep (RuntimeInvisibleAnnotations Low) = D1 ('MetaData "RuntimeInvisibleAnnotations" "Language.JVM.Attribute.Annotations" "jvm-binary-0.10.0-6UZh5809b0fJPIjalFrBq2" 'True) (C1 ('MetaCons "RuntimeInvisibleAnnotations" 'PrefixI 'True) (S1 ('MetaSel ('Just "asListOfRuntimeInvisibleAnnotations") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SizedList16 (Annotation Low)))))
type Rep (RuntimeVisibleAnnotations Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

type Rep (RuntimeVisibleAnnotations Low) = D1 ('MetaData "RuntimeVisibleAnnotations" "Language.JVM.Attribute.Annotations" "jvm-binary-0.10.0-6UZh5809b0fJPIjalFrBq2" 'True) (C1 ('MetaCons "RuntimeVisibleAnnotations" 'PrefixI 'True) (S1 ('MetaSel ('Just "asListOfRuntimeVisibleAnnotations") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SizedList16 (Annotation 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.10.0-6UZh5809b0fJPIjalFrBq2" '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 "caVisibleTypeAnnotations") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [RuntimeVisibleTypeAnnotations CodeTypeAnnotation Low]) :*: (S1 ('MetaSel ('Just "caInvisibleTypeAnnotations") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [RuntimeInvisibleTypeAnnotations CodeTypeAnnotation 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 (ExceptionTable Low) = D1 ('MetaData "ExceptionTable" "Language.JVM.Attribute.Code" "jvm-binary-0.10.0-6UZh5809b0fJPIjalFrBq2" 'False) (C1 ('MetaCons "ExceptionTable" 'PrefixI 'True) ((S1 ('MetaSel ('Just "start") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (ByteCodeRef Low)) :*: S1 ('MetaSel ('Just "end") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (ByteCodeRef Low))) :*: (S1 ('MetaSel ('Just "handler") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (ByteCodeRef Low)) :*: S1 ('MetaSel ('Just "catchType") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Ref (Maybe ClassName) Low)))))
type Rep (Code Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Code

type Rep (Code Low) = D1 ('MetaData "Code" "Language.JVM.Attribute.Code" "jvm-binary-0.10.0-6UZh5809b0fJPIjalFrBq2" 'False) (C1 ('MetaCons "Code" 'PrefixI 'True) ((S1 ('MetaSel ('Just "codeMaxStack") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Word16) :*: S1 ('MetaSel ('Just "codeMaxLocals") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Word16)) :*: (S1 ('MetaSel ('Just "codeByteCode") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (ByteCode Low)) :*: (S1 ('MetaSel ('Just "codeExceptionTable") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (SizedList16 (ExceptionTable Low))) :*: S1 ('MetaSel ('Just "codeAttributes") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Attributes CodeAttributes Low))))))
type Rep (MethodParameter Low) Source # 
Instance details

Defined in Language.JVM.Attribute.MethodParameters

type Rep (MethodParameter Low) = D1 ('MetaData "MethodParameter" "Language.JVM.Attribute.MethodParameters" "jvm-binary-0.10.0-6UZh5809b0fJPIjalFrBq2" 'False) (C1 ('MetaCons "MethodParameter" 'PrefixI 'True) (S1 ('MetaSel ('Just "parameterName") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Ref Text Low)) :*: S1 ('MetaSel ('Just "parameterAccessFlags") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (BitSet16 PAccessFlag))))
type Rep (MethodParameters Low) Source # 
Instance details

Defined in Language.JVM.Attribute.MethodParameters

type Rep (MethodParameters Low) = D1 ('MetaData "MethodParameters" "Language.JVM.Attribute.MethodParameters" "jvm-binary-0.10.0-6UZh5809b0fJPIjalFrBq2" 'True) (C1 ('MetaCons "MethodParameters" 'PrefixI 'True) (S1 ('MetaSel ('Just "methodParameters") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SizedList8 (MethodParameter 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.10.0-6UZh5809b0fJPIjalFrBq2" '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 "maAnnotationDefault") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [AnnotationDefault Low]) :*: (S1 ('MetaSel ('Just "maMethodParameters") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [MethodParameters Low]) :*: S1 ('MetaSel ('Just "maVisibleAnnotations") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [RuntimeVisibleAnnotations Low])))) :*: ((S1 ('MetaSel ('Just "maInvisibleAnnotations") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [RuntimeInvisibleAnnotations Low]) :*: (S1 ('MetaSel ('Just "maVisibleParameterAnnotations") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [RuntimeVisibleParameterAnnotations Low]) :*: S1 ('MetaSel ('Just "maInvisibleParameterAnnotations") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [RuntimeInvisibleParameterAnnotations Low]))) :*: (S1 ('MetaSel ('Just "maVisibleTypeAnnotations") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [RuntimeVisibleTypeAnnotations MethodTypeAnnotation Low]) :*: (S1 ('MetaSel ('Just "maInvisibleTypeAnnotations") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [RuntimeInvisibleTypeAnnotations MethodTypeAnnotation 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 (Method Low) = D1 ('MetaData "Method" "Language.JVM.Method" "jvm-binary-0.10.0-6UZh5809b0fJPIjalFrBq2" 'False) (C1 ('MetaCons "Method" 'PrefixI 'True) ((S1 ('MetaSel ('Just "mAccessFlags'") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (BitSet16 MAccessFlag)) :*: S1 ('MetaSel ('Just "mName") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Ref Text Low))) :*: (S1 ('MetaSel ('Just "mDescriptor") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Ref MethodDescriptor Low)) :*: S1 ('MetaSel ('Just "mAttributes") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Attributes MethodAttributes Low)))))
type Rep (FieldAttributes Low) Source # 
Instance details

Defined in Language.JVM.Field

type Rep (Field Low) Source # 
Instance details

Defined in Language.JVM.Field

type Rep (Field Low) = D1 ('MetaData "Field" "Language.JVM.Field" "jvm-binary-0.10.0-6UZh5809b0fJPIjalFrBq2" 'False) (C1 ('MetaCons "Field" 'PrefixI 'True) ((S1 ('MetaSel ('Just "fAccessFlags'") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (BitSet16 FAccessFlag)) :*: S1 ('MetaSel ('Just "fName") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Ref Text Low))) :*: (S1 ('MetaSel ('Just "fDescriptor") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Ref FieldDescriptor Low)) :*: S1 ('MetaSel ('Just "fAttributes") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Attributes FieldAttributes Low)))))
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.10.0-6UZh5809b0fJPIjalFrBq2" '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.10.0-6UZh5809b0fJPIjalFrBq2" '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 (ClassFile Low) = D1 ('MetaData "ClassFile" "Language.JVM.ClassFile" "jvm-binary-0.10.0-6UZh5809b0fJPIjalFrBq2" 'False) (C1 ('MetaCons "ClassFile" 'PrefixI 'True) (((S1 ('MetaSel ('Just "cMagicNumber") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Word32) :*: S1 ('MetaSel ('Just "cMinorVersion") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Word16)) :*: (S1 ('MetaSel ('Just "cMajorVersion") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Word16) :*: (S1 ('MetaSel ('Just "cConstantPool") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Choice (ConstantPool Low) () Low)) :*: S1 ('MetaSel ('Just "cAccessFlags'") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (BitSet16 CAccessFlag))))) :*: ((S1 ('MetaSel ('Just "cThisClass") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Ref ClassName Low)) :*: (S1 ('MetaSel ('Just "cSuperClass") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Ref ClassName Low)) :*: S1 ('MetaSel ('Just "cInterfaces") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (SizedList16 (Ref ClassName Low))))) :*: (S1 ('MetaSel ('Just "cFields'") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (SizedList16 (Field Low))) :*: (S1 ('MetaSel ('Just "cMethods'") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (SizedList16 (Method Low))) :*: S1 ('MetaSel ('Just "cAttributes") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Attributes ClassAttributes Low)))))))
type Rep (RuntimeInvisibleTypeAnnotations m Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

type Rep (RuntimeInvisibleTypeAnnotations m Low) = D1 ('MetaData "RuntimeInvisibleTypeAnnotations" "Language.JVM.Attribute.Annotations" "jvm-binary-0.10.0-6UZh5809b0fJPIjalFrBq2" 'True) (C1 ('MetaCons "RuntimeInvisibleTypeAnnotations" 'PrefixI 'True) (S1 ('MetaSel ('Just "asListOfInvisibleTypeAnnotations") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SizedList16 (TypeAnnotation m Low)))))
type Rep (RuntimeVisibleTypeAnnotations m Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

type Rep (RuntimeVisibleTypeAnnotations m Low) = D1 ('MetaData "RuntimeVisibleTypeAnnotations" "Language.JVM.Attribute.Annotations" "jvm-binary-0.10.0-6UZh5809b0fJPIjalFrBq2" 'True) (C1 ('MetaCons "RuntimeVisibleTypeAnnotations" 'PrefixI 'True) (S1 ('MetaSel ('Just "asListOfVisibleTypeAnnotations") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SizedList16 (TypeAnnotation m Low)))))
type Rep (TypeAnnotation m Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

type Rep (TypeAnnotation m Low) = D1 ('MetaData "TypeAnnotation" "Language.JVM.Attribute.Annotations" "jvm-binary-0.10.0-6UZh5809b0fJPIjalFrBq2" 'False) (C1 ('MetaCons "TypeAnnotation" 'PrefixI 'True) ((S1 ('MetaSel ('Just "typeAnnotationTarget") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (m Low)) :*: S1 ('MetaSel ('Just "typeAnnotationPath") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 TypePath)) :*: (S1 ('MetaSel ('Just "typeAnnotationType") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Ref FieldDescriptor Low)) :*: S1 ('MetaSel ('Just "typeAnnotationValuePairs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SizedList16 (ValuePair Low))))))