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

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

Language.JVM.Attribute.StackMapTable

Contents

Description

Based on the StackMapTable Attribute, as documented here.

Synopsis

Documentation

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

type DeltaOffset i = Choice Word16 Int i Source #

A delta offset

data StackMapFrame r Source #

An stack map frame

Instances
Eq (StackMapFrame High) Source # 
Instance details

Defined in Language.JVM.Attribute.StackMapTable

Eq (StackMapFrame Low) Source # 
Instance details

Defined in Language.JVM.Attribute.StackMapTable

Ord (StackMapFrame Low) Source # 
Instance details

Defined in Language.JVM.Attribute.StackMapTable

Show (StackMapFrame High) Source # 
Instance details

Defined in Language.JVM.Attribute.StackMapTable

Show (StackMapFrame Low) Source # 
Instance details

Defined in Language.JVM.Attribute.StackMapTable

Generic (StackMapFrame High) Source # 
Instance details

Defined in Language.JVM.Attribute.StackMapTable

Associated Types

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

Generic (StackMapFrame Low) Source # 
Instance details

Defined in Language.JVM.Attribute.StackMapTable

Associated Types

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

Binary (StackMapFrame Low) Source # 
Instance details

Defined in Language.JVM.Attribute.StackMapTable

NFData (StackMapFrame High) Source # 
Instance details

Defined in Language.JVM.Attribute.StackMapTable

Methods

rnf :: StackMapFrame High -> () #

NFData (StackMapFrame Low) Source # 
Instance details

Defined in Language.JVM.Attribute.StackMapTable

Methods

rnf :: StackMapFrame Low -> () #

type Rep (StackMapFrame High) Source # 
Instance details

Defined in Language.JVM.Attribute.StackMapTable

type Rep (StackMapFrame High) = D1 (MetaData "StackMapFrame" "Language.JVM.Attribute.StackMapTable" "jvm-binary-0.8.0-HpvPbNkzsQo844TuM02sMI" False) (C1 (MetaCons "StackMapFrame" PrefixI True) (S1 (MetaSel (Just "deltaOffset") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (DeltaOffset High)) :*: S1 (MetaSel (Just "frameType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (StackMapFrameType High))))
type Rep (StackMapFrame Low) Source # 
Instance details

Defined in Language.JVM.Attribute.StackMapTable

type Rep (StackMapFrame Low) = D1 (MetaData "StackMapFrame" "Language.JVM.Attribute.StackMapTable" "jvm-binary-0.8.0-HpvPbNkzsQo844TuM02sMI" False) (C1 (MetaCons "StackMapFrame" PrefixI True) (S1 (MetaSel (Just "deltaOffset") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (DeltaOffset Low)) :*: S1 (MetaSel (Just "frameType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (StackMapFrameType Low))))

data StackMapFrameType r Source #

An stack map frame type

Instances
Staged StackMapFrameType Source # 
Instance details

Defined in Language.JVM.Attribute.StackMapTable

Methods

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

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

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

Eq (StackMapFrameType High) Source # 
Instance details

Defined in Language.JVM.Attribute.StackMapTable

Eq (StackMapFrameType Low) Source # 
Instance details

Defined in Language.JVM.Attribute.StackMapTable

Ord (StackMapFrameType Low) Source # 
Instance details

Defined in Language.JVM.Attribute.StackMapTable

Show (StackMapFrameType High) Source # 
Instance details

Defined in Language.JVM.Attribute.StackMapTable

Show (StackMapFrameType Low) Source # 
Instance details

Defined in Language.JVM.Attribute.StackMapTable

Generic (StackMapFrameType High) Source # 
Instance details

Defined in Language.JVM.Attribute.StackMapTable

Associated Types

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

Generic (StackMapFrameType Low) Source # 
Instance details

Defined in Language.JVM.Attribute.StackMapTable

Associated Types

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

NFData (StackMapFrameType High) Source # 
Instance details

Defined in Language.JVM.Attribute.StackMapTable

Methods

rnf :: StackMapFrameType High -> () #

NFData (StackMapFrameType Low) Source # 
Instance details

Defined in Language.JVM.Attribute.StackMapTable

Methods

rnf :: StackMapFrameType Low -> () #

type Rep (StackMapFrameType High) Source # 
Instance details

Defined in Language.JVM.Attribute.StackMapTable

type Rep (StackMapFrameType Low) Source # 
Instance details

Defined in Language.JVM.Attribute.StackMapTable

data VerificationTypeInfo r Source #

The types info of the stack map frame.

Instances
Staged VerificationTypeInfo Source # 
Instance details

Defined in Language.JVM.Attribute.StackMapTable

Eq (VerificationTypeInfo High) Source # 
Instance details

Defined in Language.JVM.Attribute.StackMapTable

Eq (VerificationTypeInfo Low) Source # 
Instance details

Defined in Language.JVM.Attribute.StackMapTable

Ord (VerificationTypeInfo Low) Source # 
Instance details

Defined in Language.JVM.Attribute.StackMapTable

Show (VerificationTypeInfo High) Source # 
Instance details

Defined in Language.JVM.Attribute.StackMapTable

Show (VerificationTypeInfo Low) Source # 
Instance details

Defined in Language.JVM.Attribute.StackMapTable

Generic (VerificationTypeInfo High) Source # 
Instance details

Defined in Language.JVM.Attribute.StackMapTable

Associated Types

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

Generic (VerificationTypeInfo Low) Source # 
Instance details

Defined in Language.JVM.Attribute.StackMapTable

Associated Types

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

Binary (VerificationTypeInfo Low) Source # 
Instance details

Defined in Language.JVM.Attribute.StackMapTable

NFData (VerificationTypeInfo High) Source # 
Instance details

Defined in Language.JVM.Attribute.StackMapTable

Methods

rnf :: VerificationTypeInfo High -> () #

NFData (VerificationTypeInfo Low) Source # 
Instance details

Defined in Language.JVM.Attribute.StackMapTable

Methods

rnf :: VerificationTypeInfo Low -> () #

type Rep (VerificationTypeInfo High) Source # 
Instance details

Defined in Language.JVM.Attribute.StackMapTable

type Rep (VerificationTypeInfo High) = D1 (MetaData "VerificationTypeInfo" "Language.JVM.Attribute.StackMapTable" "jvm-binary-0.8.0-HpvPbNkzsQo844TuM02sMI" False) (((C1 (MetaCons "VTTop" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "VTInteger" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "VTFloat" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "VTLong" PrefixI False) (U1 :: Type -> Type))) :+: ((C1 (MetaCons "VTDouble" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "VTNull" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "VTUninitializedThis" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "VTObject" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ref JRefType High))) :+: C1 (MetaCons "VTUninitialized" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Word16))))))
type Rep (VerificationTypeInfo Low) Source # 
Instance details

Defined in Language.JVM.Attribute.StackMapTable

type Rep (VerificationTypeInfo Low) = D1 (MetaData "VerificationTypeInfo" "Language.JVM.Attribute.StackMapTable" "jvm-binary-0.8.0-HpvPbNkzsQo844TuM02sMI" False) (((C1 (MetaCons "VTTop" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "VTInteger" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "VTFloat" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "VTLong" PrefixI False) (U1 :: Type -> Type))) :+: ((C1 (MetaCons "VTDouble" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "VTNull" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "VTUninitializedThis" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "VTObject" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ref JRefType Low))) :+: C1 (MetaCons "VTUninitialized" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Word16))))))

Helper functions

offsetDelta Source #

Arguments

:: Word16

Last Index

-> Word16

Delta

-> Word16

This Index

offsetDeltaInv Source #

Arguments

:: Word16

Last Index

-> Word16

Current Index

-> Word16

Delta