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

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

Language.JVM.Method

Contents

Description

 
Synopsis

Documentation

data Method r Source #

A Method in the class-file, as described here.

Instances
Staged Method Source # 
Instance details

Defined in Language.JVM.Method

Methods

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

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

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

Eq (Method High) Source # 
Instance details

Defined in Language.JVM.Method

Eq (Method Low) Source # 
Instance details

Defined in Language.JVM.Method

Methods

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

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

Ord (Method Low) Source # 
Instance details

Defined in Language.JVM.Method

Show (Method High) Source # 
Instance details

Defined in Language.JVM.Method

Show (Method Low) Source # 
Instance details

Defined in Language.JVM.Method

Generic (Method High) Source # 
Instance details

Defined in Language.JVM.Method

Associated Types

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

Methods

from :: Method High -> Rep (Method High) x #

to :: Rep (Method High) x -> Method High #

Generic (Method Low) Source # 
Instance details

Defined in Language.JVM.Method

Associated Types

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

Methods

from :: Method Low -> Rep (Method Low) x #

to :: Rep (Method Low) x -> Method Low #

Binary (Method Low) Source # 
Instance details

Defined in Language.JVM.Method

Methods

put :: Method Low -> Put #

get :: Get (Method Low) #

putList :: [Method Low] -> Put #

NFData (Method High) Source # 
Instance details

Defined in Language.JVM.Method

Methods

rnf :: Method High -> () #

NFData (Method Low) Source # 
Instance details

Defined in Language.JVM.Method

Methods

rnf :: Method Low -> () #

type Rep (Method High) Source # 
Instance details

Defined in Language.JVM.Method

type Rep (Method Low) Source # 
Instance details

Defined in Language.JVM.Method

mAccessFlags :: Method r -> Set MAccessFlag Source #

Unpack the BitSet and get the AccessFlags as a Set.

Attributes

data MethodAttributes r Source #

Instances
Eq (MethodAttributes High) Source # 
Instance details

Defined in Language.JVM.Method

Eq (MethodAttributes Low) Source # 
Instance details

Defined in Language.JVM.Method

Ord (MethodAttributes Low) Source # 
Instance details

Defined in Language.JVM.Method

Show (MethodAttributes High) Source # 
Instance details

Defined in Language.JVM.Method

Show (MethodAttributes Low) Source # 
Instance details

Defined in Language.JVM.Method

Generic (MethodAttributes High) Source # 
Instance details

Defined in Language.JVM.Method

Associated Types

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

Generic (MethodAttributes Low) Source # 
Instance details

Defined in Language.JVM.Method

Associated Types

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

NFData (MethodAttributes High) Source # 
Instance details

Defined in Language.JVM.Method

Methods

rnf :: MethodAttributes High -> () #

NFData (MethodAttributes Low) Source # 
Instance details

Defined in Language.JVM.Method

Methods

rnf :: MethodAttributes Low -> () #

type Rep (MethodAttributes High) Source # 
Instance details

Defined in Language.JVM.Method

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

Defined in Language.JVM.Method

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

mCode :: Method High -> Maybe (Code High) Source #

Fetch the Code attribute, if any. There can only be one code attribute in a method.

mExceptions' :: Method High -> Maybe (Exceptions High) Source #

Fetch the Exceptions attribute. There can only be one exceptions attribute in a method.

mExceptions :: Method High -> [ClassName] Source #

Fetches the Exceptions attribute, but turns it into an list of exceptions. If no exceptions field where found the empty list is returned

mSignature :: Method High -> Maybe (Signature High) Source #

Fetches the Signature attribute, if any.