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

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

Language.JVM.Attribute.Annotations

Contents

Description

Based on the Annotations Attribute, as documented [here](https:/docs.oracle.comjavasespecsjvmsse8html/jvms-4.html#jvms-4.7.16).

Synopsis

Documentation

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

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

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

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

data Annotation r Source #

Instances
Staged Annotation Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Methods

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

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

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

Eq (Annotation High) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Eq (Annotation Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Ord (Annotation High) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Ord (Annotation Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Show (Annotation High) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Show (Annotation Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Generic (Annotation High) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Associated Types

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

Generic (Annotation Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Associated Types

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

Binary (Annotation Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

NFData (Annotation High) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Methods

rnf :: Annotation High -> () #

NFData (Annotation Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Methods

rnf :: Annotation Low -> () #

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.9.0-9S1OjG3yP2JAIJl8zf6L4B" 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 (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.9.0-9S1OjG3yP2JAIJl8zf6L4B" 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)))))

data ElementValue r Source #

Instances
Staged ElementValue Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Methods

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

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

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

Eq (ElementValue High) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Eq (ElementValue Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Ord (ElementValue High) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Ord (ElementValue Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Show (ElementValue High) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Show (ElementValue Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Generic (ElementValue High) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Associated Types

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

Generic (ElementValue Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Associated Types

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

Binary (ElementValue Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

NFData (ElementValue High) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Methods

rnf :: ElementValue High -> () #

NFData (ElementValue Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Methods

rnf :: ElementValue Low -> () #

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.9.0-9S1OjG3yP2JAIJl8zf6L4B" 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 (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.9.0-9S1OjG3yP2JAIJl8zf6L4B" 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))))))))

data EnumValue r Source #

Constructors

EnumValue 
Instances
Staged EnumValue Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Methods

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

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

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

Eq (EnumValue High) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Eq (EnumValue Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Ord (EnumValue High) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Ord (EnumValue Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Show (EnumValue High) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Show (EnumValue Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Generic (EnumValue High) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Associated Types

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

Generic (EnumValue Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Associated Types

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

Binary (EnumValue Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

NFData (EnumValue High) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Methods

rnf :: EnumValue High -> () #

NFData (EnumValue Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Methods

rnf :: EnumValue Low -> () #

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.9.0-9S1OjG3yP2JAIJl8zf6L4B" 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 (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.9.0-9S1OjG3yP2JAIJl8zf6L4B" 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))))

data ValuePair r Source #

Constructors

ValuePair 

Fields

Instances
Staged ValuePair Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Methods

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

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

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

Eq (ValuePair High) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Eq (ValuePair Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Ord (ValuePair High) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Ord (ValuePair Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Show (ValuePair High) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Show (ValuePair Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Generic (ValuePair High) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Associated Types

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

Generic (ValuePair Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Associated Types

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

Binary (ValuePair Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

NFData (ValuePair High) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Methods

rnf :: ValuePair High -> () #

NFData (ValuePair Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Methods

rnf :: ValuePair Low -> () #

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.9.0-9S1OjG3yP2JAIJl8zf6L4B" 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 (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.9.0-9S1OjG3yP2JAIJl8zf6L4B" 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))))

TypeAnnotations

data TypeAnnotation m r Source #

A TypeAnnotation is targeting different types.

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

Defined in Language.JVM.Attribute.Annotations

Methods

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

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

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

ByteCodeStaged m => ByteCodeStaged (TypeAnnotation m) 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

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

Ord (a High) => Ord (TypeAnnotation a High) 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

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

Defined in Language.JVM.Attribute.Annotations

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 High) => Generic (TypeAnnotation m High) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Associated Types

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

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

Defined in Language.JVM.Attribute.Annotations

Methods

rnf :: TypeAnnotation m High -> () #

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.9.0-9S1OjG3yP2JAIJl8zf6L4B" 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))))))
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.9.0-9S1OjG3yP2JAIJl8zf6L4B" 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 TypePathItem Source #

Instances
Eq TypePathItem Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Ord TypePathItem Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Show TypePathItem Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Generic TypePathItem Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Associated Types

type Rep TypePathItem :: Type -> Type #

Binary TypePathItem Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

NFData TypePathItem Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Methods

rnf :: TypePathItem -> () #

type Rep TypePathItem Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

type Rep TypePathItem = D1 (MetaData "TypePathItem" "Language.JVM.Attribute.Annotations" "jvm-binary-0.9.0-9S1OjG3yP2JAIJl8zf6L4B" False) (C1 (MetaCons "TypePathItem" PrefixI True) (S1 (MetaSel (Just "typePathKind") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 TypePathKind) :*: S1 (MetaSel (Just "typePathIndex") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Word8)))

data TypePathKind Source #

Instances
Eq TypePathKind Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Ord TypePathKind Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Show TypePathKind Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Generic TypePathKind Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Associated Types

type Rep TypePathKind :: Type -> Type #

NFData TypePathKind Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Methods

rnf :: TypePathKind -> () #

type Rep TypePathKind Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

type Rep TypePathKind = D1 (MetaData "TypePathKind" "Language.JVM.Attribute.Annotations" "jvm-binary-0.9.0-9S1OjG3yP2JAIJl8zf6L4B" False) ((C1 (MetaCons "TPathInArray" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "TPathInNested" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "TPathWildcard" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "TPathTypeArgument" PrefixI False) (U1 :: Type -> Type)))

newtype 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.9.0-9S1OjG3yP2JAIJl8zf6L4B" 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.9.0-9S1OjG3yP2JAIJl8zf6L4B" True) (C1 (MetaCons "RuntimeVisibleTypeAnnotations" PrefixI True) (S1 (MetaSel (Just "asListOfVisibleTypeAnnotations") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (SizedList16 (TypeAnnotation m High)))))

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

data ClassTypeAnnotation r Source #

From here

Constructors

ClassTypeParameterDeclaration !TypeParameterTarget

type parameter declaration of generic class or interface (0x00)

ClassSuperType !SupertypeTarget

type in extends clause of class or interface declaration, or in implements clause of interface declaration (0x10)

ClassBoundTypeParameterDeclaration !TypeParameterBoundTarget

type in bound of type parameter declaration of generic class or interface (0x11)

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 High) 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.9.0-9S1OjG3yP2JAIJl8zf6L4B" 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.9.0-9S1OjG3yP2JAIJl8zf6L4B" 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 #

Constructors

MethodTypeParameterDeclaration !TypeParameterTarget

type parameter declaration of generic method or constructor (0x01)

MethodBoundTypeParameterDeclaration !TypeParameterBoundTarget

type in bound of type parameter declaration of generic method or constructor (0x12)

MethodReturnType

return type of method or constructor (0x14)

MethodReceiverType

receiver type of method or constructor (0x15)

MethodFormalParameter !FormalParameterTarget

type in formal parameter declaration of method, constructor, or lambda expression (0x16)

MethodThrowsClause !ThrowsTarget

type in throws clause of method or constructor (0x17)

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 High) 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.9.0-9S1OjG3yP2JAIJl8zf6L4B" 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.9.0-9S1OjG3yP2JAIJl8zf6L4B" 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 #

Constructors

FieldTypeAnnotation

type in field declaration (0x13)

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 High) 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.9.0-9S1OjG3yP2JAIJl8zf6L4B" 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.9.0-9S1OjG3yP2JAIJl8zf6L4B" False) (C1 (MetaCons "FieldTypeAnnotation" PrefixI False) (U1 :: Type -> Type))

data CodeTypeAnnotation r Source #

Constructors

LocalVariableDeclaration !(LocalvarTarget r)

type in local variable declaration (0x40)

ResourceVariableDeclaration !(LocalvarTarget r)

type in resource variable declaration (0x41)

ExceptionParameterDeclaration !CatchTarget

type in exception parameter declaration (0x42)

InstanceOfExpression !(OffsetTarget r)

type in instanceof expression (0x43)

NewExpression !(OffsetTarget r)

type in new expression (0x44)

NewMethodReferenceExpression !(OffsetTarget r)

type in method reference expression using ::new (0x45)

IdentifierMethodReferenceExpression !(OffsetTarget r)

type in method reference expression using ::Identifier (0x46)

CastExpression !(TypeArgumentTarget r)

type in cast expression (0x47)

ConstructorExpression !(TypeArgumentTarget r)

type argument for generic constructor in new expression or explicit constructor invocation statement (0x48)

MethodIncovationExpression !(TypeArgumentTarget r)

type argument for generic method in method invocation expression (0x49)

GenericNewMethodReferenceExpression !(TypeArgumentTarget r)

type argument for generic constructor in method reference expression using ::new (0x4A)

GenericIdentifierwMethodReferenceExpression !(TypeArgumentTarget r)

type argument for generic method in method reference expression using ::Identifier (0x4B)

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 High) 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.9.0-9S1OjG3yP2JAIJl8zf6L4B" 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.9.0-9S1OjG3yP2JAIJl8zf6L4B" 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 TypeParameterTarget = Word8 Source #

The TypeParameterTarget item indicates that an annotation appears on the declaration of the i'th type parameter of a generic class, generic interface, generic method, or generic constructor.

type SupertypeTarget = Word16 Source #

The SupertypeTarget item indicates that an annotation appears on a type in the extends or implements clause of a class or interface declaration.

A value of 65535 specifies that the annotation appears on the superclass in an extends clause of a class declaration.

isInExtendsClause :: SupertypeTarget -> Bool Source #

Check if the SupertypeTarget is in the extends clauses

data TypeParameterBoundTarget Source #

The TypeParameterBoundTarget item indicates that an annotation appears on the i'th bound of the j'th type parameter declaration of a generic class, interface, method, or constructor.

Instances
Eq TypeParameterBoundTarget Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Ord TypeParameterBoundTarget Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Show TypeParameterBoundTarget Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Generic TypeParameterBoundTarget Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Associated Types

type Rep TypeParameterBoundTarget :: Type -> Type #

Binary TypeParameterBoundTarget Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

NFData TypeParameterBoundTarget Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

type Rep TypeParameterBoundTarget Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

type Rep TypeParameterBoundTarget = D1 (MetaData "TypeParameterBoundTarget" "Language.JVM.Attribute.Annotations" "jvm-binary-0.9.0-9S1OjG3yP2JAIJl8zf6L4B" False) (C1 (MetaCons "TypeParameterBoundTarget" PrefixI True) (S1 (MetaSel (Just "typeParameter") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 TypeParameterTarget) :*: S1 (MetaSel (Just "typeBound") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Word8)))

type FormalParameterTarget = Word8 Source #

The FormalParameterTarget item indicates that an annotation appears on the type in a formal parameter declaration of a method, constructor, or lambda expression. The target is 0-indexed.

type ThrowsTarget = Word16 Source #

The ThrowsTarget item indicates that an annotation appears on the i'th type in the throws clause of a method or constructor declaration.

The value is an index into the Exceptions attribute

type LocalvarTarget r = SizedList16 (LocalvarEntry r) Source #

The LocalvarTarget item indicates that an annotation appears on the type in a local variable declaration, including a variable declared as a resource in a try-with-resources statement.

The table is needed because a variable might span multiple live ranges.

data LocalvarEntry r Source #

An entry in the Localvar Table

Instances
ByteCodeStaged LocalvarEntry Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Eq (LocalvarEntry High) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Eq (LocalvarEntry Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Ord (LocalvarEntry High) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Ord (LocalvarEntry Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Show (LocalvarEntry High) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Show (LocalvarEntry Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Generic (LocalvarEntry High) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Associated Types

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

Generic (LocalvarEntry Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Associated Types

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

Binary (LocalvarEntry Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

NFData (LocalvarEntry High) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Methods

rnf :: LocalvarEntry High -> () #

NFData (LocalvarEntry Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Methods

rnf :: LocalvarEntry Low -> () #

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.9.0-9S1OjG3yP2JAIJl8zf6L4B" 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 (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.9.0-9S1OjG3yP2JAIJl8zf6L4B" 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 CatchTarget = Word16 Source #

The CatchTarget item indicates that an annotation appears on the i'th type in an exception parameter declaration.

type OffsetTarget r = ByteCodeRef r Source #

The OffsetTarget item indicates that an annotation appears on either the type in an instanceof expression or a new expression, or the type before the :: in a method reference expression.

data TypeArgumentTarget r Source #

The TypeArgumentTarget item indicates that an annotation appears either on the i'th type in a cast expression, or on the i'th type argument in the explicit type argument list for any of the following: a new expression, an explicit constructor invocation statement, a method invocation expression, or a method reference expression.

Instances
ByteCodeStaged TypeArgumentTarget Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Eq (TypeArgumentTarget High) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Eq (TypeArgumentTarget Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Ord (TypeArgumentTarget High) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Ord (TypeArgumentTarget Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Show (TypeArgumentTarget High) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Show (TypeArgumentTarget Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Generic (TypeArgumentTarget High) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Associated Types

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

Generic (TypeArgumentTarget Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Associated Types

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

Binary (TypeArgumentTarget Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

NFData (TypeArgumentTarget High) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Methods

rnf :: TypeArgumentTarget High -> () #

NFData (TypeArgumentTarget Low) Source # 
Instance details

Defined in Language.JVM.Attribute.Annotations

Methods

rnf :: TypeArgumentTarget Low -> () #

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.9.0-9S1OjG3yP2JAIJl8zf6L4B" 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 (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.9.0-9S1OjG3yP2JAIJl8zf6L4B" 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)))

AnnotationDefault

newtype 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.

Constructors

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