jvm-binary-0.5.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.5.0-8tjUXfOvOFm5evlZ3bpMMl" 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.5.0-8tjUXfOvOFm5evlZ3bpMMl" 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.5.0-8tjUXfOvOFm5evlZ3bpMMl" 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.5.0-8tjUXfOvOFm5evlZ3bpMMl" 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.5.0-8tjUXfOvOFm5evlZ3bpMMl" 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.5.0-8tjUXfOvOFm5evlZ3bpMMl" 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.5.0-8tjUXfOvOFm5evlZ3bpMMl" 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.5.0-8tjUXfOvOFm5evlZ3bpMMl" True) (C1 (MetaCons "StackMapTable" PrefixI True) (S1 (MetaSel (Just "stackMapTable") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Choice (SizedList16 (StackMapFrame Low)) [StackMapFrame High] High))))
type Rep (StackMapTable Low) Source # 
Instance details

Defined in Language.JVM.Attribute.StackMapTable

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

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