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

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

Language.JVM.Attribute

Contents

Description

This is the main module for accessing all kinds of Attributes.

Synopsis

Documentation

Subattributes

data BootstrapMethods r Source #

Is a list of bootstrapped methods.

Instances
Staged BootstrapMethods Source # 
Instance details

Defined in Language.JVM.Attribute.BootstrapMethods

Methods

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

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

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

Eq (BootstrapMethods High) Source # 
Instance details

Defined in Language.JVM.Attribute.BootstrapMethods

Eq (BootstrapMethods Low) Source # 
Instance details

Defined in Language.JVM.Attribute.BootstrapMethods

Ord (BootstrapMethods Low) Source # 
Instance details

Defined in Language.JVM.Attribute.BootstrapMethods

Show (BootstrapMethods High) Source # 
Instance details

Defined in Language.JVM.Attribute.BootstrapMethods

Show (BootstrapMethods Low) Source # 
Instance details

Defined in Language.JVM.Attribute.BootstrapMethods

Generic (BootstrapMethods High) Source # 
Instance details

Defined in Language.JVM.Attribute.BootstrapMethods

Associated Types

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

Generic (BootstrapMethods Low) Source # 
Instance details

Defined in Language.JVM.Attribute.BootstrapMethods

Associated Types

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

Binary (BootstrapMethods Low) Source # 
Instance details

Defined in Language.JVM.Attribute.BootstrapMethods

NFData (BootstrapMethods High) Source # 
Instance details

Defined in Language.JVM.Attribute.BootstrapMethods

Methods

rnf :: BootstrapMethods High -> () #

NFData (BootstrapMethods Low) Source # 
Instance details

Defined in Language.JVM.Attribute.BootstrapMethods

Methods

rnf :: BootstrapMethods Low -> () #

IsAttribute (BootstrapMethods Low) Source #

BootstrapMethods is an Attribute.

Instance details

Defined in Language.JVM.Attribute.BootstrapMethods

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.8.0-HpvPbNkzsQo844TuM02sMI" True) (C1 (MetaCons "BootstrapMethods" PrefixI True) (S1 (MetaSel (Just "methods'") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (SizedList16 (BootstrapMethod High)))))
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.8.0-HpvPbNkzsQo844TuM02sMI" True) (C1 (MetaCons "BootstrapMethods" PrefixI True) (S1 (MetaSel (Just "methods'") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (SizedList16 (BootstrapMethod Low)))))

data Code r Source #

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

Instances
Staged Code Source # 
Instance details

Defined in Language.JVM.Attribute.Code

Methods

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

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

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

Eq (Code High) Source # 
Instance details

Defined in Language.JVM.Attribute.Code

Methods

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

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

Eq (Code Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Code

Methods

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

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

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 #

Show (Code High) 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 #

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

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 #

NFData (Code High) Source # 
Instance details

Defined in Language.JVM.Attribute.Code

Methods

rnf :: Code High -> () #

NFData (Code Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Code

Methods

rnf :: Code Low -> () #

IsAttribute (Code Low) Source #

Code is an Attribute.

Instance details

Defined in Language.JVM.Attribute.Code

type Rep (Code High) Source # 
Instance details

Defined in Language.JVM.Attribute.Code

type Rep (Code Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Code

data ConstantValue r Source #

A constant value is just a index into the constant pool.

Instances
Staged ConstantValue Source # 
Instance details

Defined in Language.JVM.Attribute.ConstantValue

Methods

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

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

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

Eq (ConstantValue High) Source # 
Instance details

Defined in Language.JVM.Attribute.ConstantValue

Eq (ConstantValue Low) Source # 
Instance details

Defined in Language.JVM.Attribute.ConstantValue

Ord (ConstantValue Low) Source # 
Instance details

Defined in Language.JVM.Attribute.ConstantValue

Show (ConstantValue High) Source # 
Instance details

Defined in Language.JVM.Attribute.ConstantValue

Show (ConstantValue Low) Source # 
Instance details

Defined in Language.JVM.Attribute.ConstantValue

Generic (ConstantValue High) Source # 
Instance details

Defined in Language.JVM.Attribute.ConstantValue

Associated Types

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

Generic (ConstantValue Low) Source # 
Instance details

Defined in Language.JVM.Attribute.ConstantValue

Associated Types

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

Binary (ConstantValue Low) Source # 
Instance details

Defined in Language.JVM.Attribute.ConstantValue

NFData (ConstantValue High) Source # 
Instance details

Defined in Language.JVM.Attribute.ConstantValue

Methods

rnf :: ConstantValue High -> () #

NFData (ConstantValue Low) Source # 
Instance details

Defined in Language.JVM.Attribute.ConstantValue

Methods

rnf :: ConstantValue Low -> () #

IsAttribute (ConstantValue Low) Source #

ConstantValue is an Attribute.

Instance details

Defined in Language.JVM.Attribute.ConstantValue

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.8.0-HpvPbNkzsQo844TuM02sMI" False) (C1 (MetaCons "ConstantValue" PrefixI True) (S1 (MetaSel (Just "constantValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Ref JValue High))))
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.8.0-HpvPbNkzsQo844TuM02sMI" False) (C1 (MetaCons "ConstantValue" PrefixI True) (S1 (MetaSel (Just "constantValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Ref JValue Low))))

data Exceptions r Source #

An Exceptions attribute is a list of references into the constant pool.

Instances
Staged Exceptions Source # 
Instance details

Defined in Language.JVM.Attribute.Exceptions

Methods

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

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

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

Eq (Exceptions High) Source # 
Instance details

Defined in Language.JVM.Attribute.Exceptions

Eq (Exceptions Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Exceptions

Ord (Exceptions Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Exceptions

Show (Exceptions High) Source # 
Instance details

Defined in Language.JVM.Attribute.Exceptions

Show (Exceptions Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Exceptions

Generic (Exceptions High) Source # 
Instance details

Defined in Language.JVM.Attribute.Exceptions

Associated Types

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

Generic (Exceptions Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Exceptions

Associated Types

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

Binary (Exceptions Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Exceptions

NFData (Exceptions High) Source # 
Instance details

Defined in Language.JVM.Attribute.Exceptions

Methods

rnf :: Exceptions High -> () #

NFData (Exceptions Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Exceptions

Methods

rnf :: Exceptions Low -> () #

IsAttribute (Exceptions Low) Source #

Exceptions is an Attribute.

Instance details

Defined in Language.JVM.Attribute.Exceptions

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.8.0-HpvPbNkzsQo844TuM02sMI" True) (C1 (MetaCons "Exceptions" PrefixI True) (S1 (MetaSel (Just "exceptions") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (SizedList16 (Ref ClassName High)))))
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.8.0-HpvPbNkzsQo844TuM02sMI" True) (C1 (MetaCons "Exceptions" PrefixI True) (S1 (MetaSel (Just "exceptions") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (SizedList16 (Ref ClassName Low)))))

data LineNumberTable r Source #

The LineNumberTable is just a mapping from offsets to linenumbers.

Instances
ByteCodeStaged LineNumberTable Source # 
Instance details

Defined in Language.JVM.Attribute.LineNumberTable

Eq (LineNumberTable r) Source # 
Instance details

Defined in Language.JVM.Attribute.LineNumberTable

Ord (LineNumberTable r) Source # 
Instance details

Defined in Language.JVM.Attribute.LineNumberTable

Show (LineNumberTable r) Source # 
Instance details

Defined in Language.JVM.Attribute.LineNumberTable

Generic (LineNumberTable r) Source # 
Instance details

Defined in Language.JVM.Attribute.LineNumberTable

Associated Types

type Rep (LineNumberTable r) :: Type -> Type #

Binary (LineNumberTable Low) Source # 
Instance details

Defined in Language.JVM.Attribute.LineNumberTable

NFData (LineNumberTable r) Source # 
Instance details

Defined in Language.JVM.Attribute.LineNumberTable

Methods

rnf :: LineNumberTable r -> () #

IsAttribute (LineNumberTable Low) Source #

Signature is an Attribute.

Instance details

Defined in Language.JVM.Attribute.LineNumberTable

type Rep (LineNumberTable r) Source # 
Instance details

Defined in Language.JVM.Attribute.LineNumberTable

type Rep (LineNumberTable r) = D1 (MetaData "LineNumberTable" "Language.JVM.Attribute.LineNumberTable" "jvm-binary-0.8.0-HpvPbNkzsQo844TuM02sMI" True) (C1 (MetaCons "LineNumberTable" PrefixI True) (S1 (MetaSel (Just "lineNumberTable") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (IntMap LineNumber))))

data StackMapTable r Source #

An Exceptions attribute is a list of references into the constant pool.

Instances
ByteCodeStaged StackMapTable Source # 
Instance details

Defined in Language.JVM.Attribute.StackMapTable

Eq (StackMapTable High) Source # 
Instance details

Defined in Language.JVM.Attribute.StackMapTable

Eq (StackMapTable Low) Source # 
Instance details

Defined in Language.JVM.Attribute.StackMapTable

Ord (StackMapTable Low) Source # 
Instance details

Defined in Language.JVM.Attribute.StackMapTable

Show (StackMapTable High) Source # 
Instance details

Defined in Language.JVM.Attribute.StackMapTable

Show (StackMapTable Low) Source # 
Instance details

Defined in Language.JVM.Attribute.StackMapTable

Generic (StackMapTable High) Source # 
Instance details

Defined in Language.JVM.Attribute.StackMapTable

Associated Types

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

Generic (StackMapTable Low) Source # 
Instance details

Defined in Language.JVM.Attribute.StackMapTable

Associated Types

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

Binary (StackMapTable Low) Source # 
Instance details

Defined in Language.JVM.Attribute.StackMapTable

NFData (StackMapTable High) Source # 
Instance details

Defined in Language.JVM.Attribute.StackMapTable

Methods

rnf :: StackMapTable High -> () #

NFData (StackMapTable Low) Source # 
Instance details

Defined in Language.JVM.Attribute.StackMapTable

Methods

rnf :: StackMapTable Low -> () #

IsAttribute (StackMapTable Low) Source #

StackMapTable is an Attribute.

Instance details

Defined in Language.JVM.Attribute.StackMapTable

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.8.0-HpvPbNkzsQo844TuM02sMI" True) (C1 (MetaCons "StackMapTable" PrefixI True) (S1 (MetaSel (Just "stackMapTable") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Choice (SizedList16 (StackMapFrame Low)) [StackMapFrame High] High))))
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.8.0-HpvPbNkzsQo844TuM02sMI" True) (C1 (MetaCons "StackMapTable" PrefixI True) (S1 (MetaSel (Just "stackMapTable") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Choice (SizedList16 (StackMapFrame Low)) [StackMapFrame High] Low))))

data Signature a Source #

Instances
Staged Signature Source # 
Instance details

Defined in Language.JVM.Attribute.Signature

Methods

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

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

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

Eq (Signature High) Source # 
Instance details

Defined in Language.JVM.Attribute.Signature

Eq (Signature Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Signature

Ord (Signature Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Signature

Show (Signature High) Source # 
Instance details

Defined in Language.JVM.Attribute.Signature

Show (Signature Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Signature

Generic (Signature High) Source # 
Instance details

Defined in Language.JVM.Attribute.Signature

Associated Types

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

Generic (Signature Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Signature

Associated Types

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

Binary (Signature Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Signature

NFData (Signature High) Source # 
Instance details

Defined in Language.JVM.Attribute.Signature

Methods

rnf :: Signature High -> () #

NFData (Signature Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Signature

Methods

rnf :: Signature Low -> () #

IsAttribute (Signature Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Signature

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.8.0-HpvPbNkzsQo844TuM02sMI" True) (C1 (MetaCons "Signature" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ref Text High))))
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.8.0-HpvPbNkzsQo844TuM02sMI" True) (C1 (MetaCons "Signature" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ref Text Low))))

data RuntimeVisibleAnnotations r Source #

Instances
Staged RuntimeVisibleAnnotations Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Eq (RuntimeVisibleAnnotations High) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Eq (RuntimeVisibleAnnotations Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Ord (RuntimeVisibleAnnotations Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Show (RuntimeVisibleAnnotations High) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Show (RuntimeVisibleAnnotations Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Generic (RuntimeVisibleAnnotations High) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Associated Types

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

Generic (RuntimeVisibleAnnotations Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Associated Types

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

Binary (RuntimeVisibleAnnotations Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

NFData (RuntimeVisibleAnnotations High) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

NFData (RuntimeVisibleAnnotations Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

IsAttribute (RuntimeVisibleAnnotations Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

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.8.0-HpvPbNkzsQo844TuM02sMI" True) (C1 (MetaCons "RuntimeVisibleAnnotations" PrefixI True) (S1 (MetaSel (Just "asListOfRuntimeVisibleAnnotations") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (SizedList16 (Annotation High)))))
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.8.0-HpvPbNkzsQo844TuM02sMI" True) (C1 (MetaCons "RuntimeVisibleAnnotations" PrefixI True) (S1 (MetaSel (Just "asListOfRuntimeVisibleAnnotations") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (SizedList16 (Annotation Low)))))

data RuntimeInvisibleAnnotations r Source #

Instances
Staged RuntimeInvisibleAnnotations Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Eq (RuntimeInvisibleAnnotations High) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Eq (RuntimeInvisibleAnnotations Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Ord (RuntimeInvisibleAnnotations Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Show (RuntimeInvisibleAnnotations High) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Show (RuntimeInvisibleAnnotations Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Generic (RuntimeInvisibleAnnotations High) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Associated Types

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

Generic (RuntimeInvisibleAnnotations Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Associated Types

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

Binary (RuntimeInvisibleAnnotations Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

NFData (RuntimeInvisibleAnnotations High) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

NFData (RuntimeInvisibleAnnotations Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

IsAttribute (RuntimeInvisibleAnnotations Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

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.8.0-HpvPbNkzsQo844TuM02sMI" True) (C1 (MetaCons "RuntimeInvisibleAnnotations" PrefixI True) (S1 (MetaSel (Just "asListOfRuntimeInvisibleAnnotations") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (SizedList16 (Annotation High)))))
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.8.0-HpvPbNkzsQo844TuM02sMI" True) (C1 (MetaCons "RuntimeInvisibleAnnotations" PrefixI True) (S1 (MetaSel (Just "asListOfRuntimeInvisibleAnnotations") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (SizedList16 (Annotation Low)))))

data RuntimeVisibleParameterAnnotations r Source #

Instances
Staged RuntimeVisibleParameterAnnotations Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Eq (RuntimeVisibleParameterAnnotations High) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Eq (RuntimeVisibleParameterAnnotations Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Ord (RuntimeVisibleParameterAnnotations Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Show (RuntimeVisibleParameterAnnotations High) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

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

Defined in Language.JVM.Attribute.Annotations

Associated Types

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

Binary (RuntimeVisibleParameterAnnotations Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

NFData (RuntimeVisibleParameterAnnotations High) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

NFData (RuntimeVisibleParameterAnnotations Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

IsAttribute (RuntimeVisibleParameterAnnotations Low) Source #

RuntimeVisibleParameterAnnotations is an Attribute.

Instance details

Defined in Language.JVM.Attribute.Annotations

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.8.0-HpvPbNkzsQo844TuM02sMI" True) (C1 (MetaCons "RuntimeVisibleParameterAnnotations" PrefixI True) (S1 (MetaSel (Just "asListOfVisibleParameterAnnotations") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (SizedList8 (SizedList16 (Annotation High))))))
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.8.0-HpvPbNkzsQo844TuM02sMI" True) (C1 (MetaCons "RuntimeVisibleParameterAnnotations" PrefixI True) (S1 (MetaSel (Just "asListOfVisibleParameterAnnotations") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (SizedList8 (SizedList16 (Annotation Low))))))

data RuntimeInvisibleParameterAnnotations r Source #

Instances
Staged RuntimeInvisibleParameterAnnotations Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Eq (RuntimeInvisibleParameterAnnotations High) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Eq (RuntimeInvisibleParameterAnnotations Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Ord (RuntimeInvisibleParameterAnnotations Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Show (RuntimeInvisibleParameterAnnotations High) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Show (RuntimeInvisibleParameterAnnotations Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Generic (RuntimeInvisibleParameterAnnotations High) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Generic (RuntimeInvisibleParameterAnnotations Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Associated Types

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

Binary (RuntimeInvisibleParameterAnnotations Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

NFData (RuntimeInvisibleParameterAnnotations High) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

NFData (RuntimeInvisibleParameterAnnotations 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

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.8.0-HpvPbNkzsQo844TuM02sMI" True) (C1 (MetaCons "RuntimeInvisibleParameterAnnotations" PrefixI True) (S1 (MetaSel (Just "asListOfInvisibleParameterAnnotations") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (SizedList8 (SizedList16 (Annotation High))))))
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.8.0-HpvPbNkzsQo844TuM02sMI" True) (C1 (MetaCons "RuntimeInvisibleParameterAnnotations" PrefixI True) (S1 (MetaSel (Just "asListOfInvisibleParameterAnnotations") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (SizedList8 (SizedList16 (Annotation Low))))))

data RuntimeVisibleTypeAnnotations m r Source #

Instances
Staged m => Staged (RuntimeVisibleTypeAnnotations m) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

ByteCodeStaged m => ByteCodeStaged (RuntimeVisibleTypeAnnotations m) 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 High) => Eq (RuntimeVisibleTypeAnnotations m High) 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

Show (m Low) => Show (RuntimeVisibleTypeAnnotations m Low) 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

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 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 Low), Binary (m Low)) => Binary (RuntimeVisibleTypeAnnotations 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 High), NFData (m High)) => NFData (RuntimeVisibleTypeAnnotations m High) Source # 
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 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.8.0-HpvPbNkzsQo844TuM02sMI" True) (C1 (MetaCons "RuntimeVisibleTypeAnnotations" PrefixI True) (S1 (MetaSel (Just "asListOfVisibleTypeAnnotations") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (SizedList16 (TypeAnnotation m Low)))))
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.8.0-HpvPbNkzsQo844TuM02sMI" True) (C1 (MetaCons "RuntimeVisibleTypeAnnotations" PrefixI True) (S1 (MetaSel (Just "asListOfVisibleTypeAnnotations") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (SizedList16 (TypeAnnotation m High)))))

data RuntimeInvisibleTypeAnnotations m r Source #

Instances
Staged m => Staged (RuntimeInvisibleTypeAnnotations m) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

ByteCodeStaged m => ByteCodeStaged (RuntimeInvisibleTypeAnnotations m) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

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

Defined in Language.JVM.Attribute.Annotations

Eq (m High) => Eq (RuntimeInvisibleTypeAnnotations m High) 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

Show (m Low) => Show (RuntimeInvisibleTypeAnnotations m Low) 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

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 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 Low), Binary (m Low)) => Binary (RuntimeInvisibleTypeAnnotations 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 High), NFData (m High)) => NFData (RuntimeInvisibleTypeAnnotations m High) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

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

RuntimeInvisibleTypeAnnotations is an Attribute.

Instance details

Defined in Language.JVM.Attribute.Annotations

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.8.0-HpvPbNkzsQo844TuM02sMI" True) (C1 (MetaCons "RuntimeInvisibleTypeAnnotations" PrefixI True) (S1 (MetaSel (Just "asListOfInvisibleTypeAnnotations") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (SizedList16 (TypeAnnotation m Low)))))
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.8.0-HpvPbNkzsQo844TuM02sMI" True) (C1 (MetaCons "RuntimeInvisibleTypeAnnotations" PrefixI True) (S1 (MetaSel (Just "asListOfInvisibleTypeAnnotations") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (SizedList16 (TypeAnnotation m High)))))

data ClassTypeAnnotation r Source #

From here

Instances
Staged ClassTypeAnnotation Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Eq (ClassTypeAnnotation High) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Eq (ClassTypeAnnotation Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Ord (ClassTypeAnnotation Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Show (ClassTypeAnnotation High) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Show (ClassTypeAnnotation Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Generic (ClassTypeAnnotation High) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Associated Types

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

Generic (ClassTypeAnnotation Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Associated Types

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

Binary (ClassTypeAnnotation Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

NFData (ClassTypeAnnotation High) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Methods

rnf :: ClassTypeAnnotation High -> () #

NFData (ClassTypeAnnotation Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Methods

rnf :: ClassTypeAnnotation Low -> () #

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.8.0-HpvPbNkzsQo844TuM02sMI" 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 (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.8.0-HpvPbNkzsQo844TuM02sMI" 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))))

data MethodTypeAnnotation r Source #

Instances
Staged MethodTypeAnnotation Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Eq (MethodTypeAnnotation High) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Eq (MethodTypeAnnotation Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Ord (MethodTypeAnnotation Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Show (MethodTypeAnnotation High) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Show (MethodTypeAnnotation Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Generic (MethodTypeAnnotation High) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Associated Types

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

Generic (MethodTypeAnnotation Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Associated Types

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

Binary (MethodTypeAnnotation Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

NFData (MethodTypeAnnotation High) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Methods

rnf :: MethodTypeAnnotation High -> () #

NFData (MethodTypeAnnotation Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Methods

rnf :: MethodTypeAnnotation Low -> () #

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.8.0-HpvPbNkzsQo844TuM02sMI" 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 (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.8.0-HpvPbNkzsQo844TuM02sMI" 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)))))

data FieldTypeAnnotation r Source #

Instances
Staged FieldTypeAnnotation Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Eq (FieldTypeAnnotation High) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Eq (FieldTypeAnnotation Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Ord (FieldTypeAnnotation Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Show (FieldTypeAnnotation High) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Show (FieldTypeAnnotation Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Generic (FieldTypeAnnotation High) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Associated Types

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

Generic (FieldTypeAnnotation Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Associated Types

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

Binary (FieldTypeAnnotation Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

NFData (FieldTypeAnnotation High) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Methods

rnf :: FieldTypeAnnotation High -> () #

NFData (FieldTypeAnnotation Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Methods

rnf :: FieldTypeAnnotation Low -> () #

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.8.0-HpvPbNkzsQo844TuM02sMI" False) (C1 (MetaCons "FieldTypeAnnotation" PrefixI False) (U1 :: Type -> Type))
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.8.0-HpvPbNkzsQo844TuM02sMI" False) (C1 (MetaCons "FieldTypeAnnotation" PrefixI False) (U1 :: Type -> Type))

data CodeTypeAnnotation r Source #

Instances
ByteCodeStaged CodeTypeAnnotation Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Eq (CodeTypeAnnotation High) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Eq (CodeTypeAnnotation Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Ord (CodeTypeAnnotation Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Show (CodeTypeAnnotation High) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Show (CodeTypeAnnotation Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Generic (CodeTypeAnnotation High) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Associated Types

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

Generic (CodeTypeAnnotation Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Associated Types

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

Binary (CodeTypeAnnotation Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

NFData (CodeTypeAnnotation High) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Methods

rnf :: CodeTypeAnnotation High -> () #

NFData (CodeTypeAnnotation Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Methods

rnf :: CodeTypeAnnotation Low -> () #

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.8.0-HpvPbNkzsQo844TuM02sMI" 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 (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.8.0-HpvPbNkzsQo844TuM02sMI" 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)))))))

data AnnotationDefault r Source #

The AnnotationDefault attribute is a variable-length attribute in the attributes table of certain method_info structures (§4.6), namely those representing elements of annotation types (JLS §9.6.1). The AnnotationDefault attribute records the default value (JLS §9.6.2) for the element represented by the method_info structure. The Java Virtual Machine must make this default value available so it can be applied by appropriate reflective APIs.

Instances
Staged AnnotationDefault Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Methods

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

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

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

Eq (AnnotationDefault High) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Eq (AnnotationDefault Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Ord (AnnotationDefault Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Show (AnnotationDefault High) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Show (AnnotationDefault Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Generic (AnnotationDefault High) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Associated Types

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

Generic (AnnotationDefault Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Associated Types

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

Binary (AnnotationDefault Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

NFData (AnnotationDefault High) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Methods

rnf :: AnnotationDefault High -> () #

NFData (AnnotationDefault Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Methods

rnf :: AnnotationDefault Low -> () #

IsAttribute (AnnotationDefault Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

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.8.0-HpvPbNkzsQo844TuM02sMI" True) (C1 (MetaCons "AnnotationDefault" PrefixI True) (S1 (MetaSel (Just "defaultValue") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (ElementValue High))))
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.8.0-HpvPbNkzsQo844TuM02sMI" True) (C1 (MetaCons "AnnotationDefault" PrefixI True) (S1 (MetaSel (Just "defaultValue") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (ElementValue Low))))