jvm-binary-0.1.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.BootstrapMethods

Description

Based on the BootstrapMethods Attribute, as documented [here](http:/docs.oracle.comjavasespecsjvmsse8html/jvms-4.html#jvms-4.7.23).

Synopsis

Documentation

newtype BootstrapMethods r Source #

Is a list of bootstrapped methods.

Instances

Staged BootstrapMethods Source # 

Methods

stage :: LabelM m => (forall (s' :: * -> *). 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 # 
Eq (BootstrapMethods Low) Source # 
Ord (BootstrapMethods Low) Source # 
Show (BootstrapMethods High) Source # 
Show (BootstrapMethods Low) Source # 
Generic (BootstrapMethods High) Source # 
Generic (BootstrapMethods Low) Source # 
Binary (BootstrapMethods Low) Source # 
NFData (BootstrapMethods High) Source # 

Methods

rnf :: BootstrapMethods High -> () #

NFData (BootstrapMethods Low) Source # 

Methods

rnf :: BootstrapMethods Low -> () #

IsAttribute (BootstrapMethods Low) Source #

BootstrapMethods is an Attribute.

type Rep (BootstrapMethods High) Source # 
type Rep (BootstrapMethods High) = D1 * (MetaData "BootstrapMethods" "Language.JVM.Attribute.BootstrapMethods" "jvm-binary-0.1.0-JJ8Rr7ERir79pQaBJvdiXV" True) (C1 * (MetaCons "BootstrapMethods" PrefixI True) (S1 * (MetaSel (Just Symbol "methods'") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (SizedList16 (BootstrapMethod High)))))
type Rep (BootstrapMethods Low) Source # 
type Rep (BootstrapMethods Low) = D1 * (MetaData "BootstrapMethods" "Language.JVM.Attribute.BootstrapMethods" "jvm-binary-0.1.0-JJ8Rr7ERir79pQaBJvdiXV" True) (C1 * (MetaCons "BootstrapMethods" PrefixI True) (S1 * (MetaSel (Just Symbol "methods'") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (SizedList16 (BootstrapMethod Low)))))

methods :: BootstrapMethods r -> [BootstrapMethod r] Source #

The methods as list

data BootstrapMethod r Source #

A bootstraped methods.

Constructors

BootstrapMethod 

Instances

Staged BootstrapMethod Source # 

Methods

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

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

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

Eq (BootstrapMethod High) Source # 
Eq (BootstrapMethod Low) Source # 
Ord (BootstrapMethod Low) Source # 
Show (BootstrapMethod High) Source # 
Show (BootstrapMethod Low) Source # 
Generic (BootstrapMethod High) Source # 
Generic (BootstrapMethod Low) Source # 

Associated Types

type Rep (BootstrapMethod Low) :: * -> * #

Binary (BootstrapMethod Low) Source # 
NFData (BootstrapMethod High) Source # 

Methods

rnf :: BootstrapMethod High -> () #

NFData (BootstrapMethod Low) Source # 

Methods

rnf :: BootstrapMethod Low -> () #

type Rep (BootstrapMethod High) Source # 
type Rep (BootstrapMethod High) = D1 * (MetaData "BootstrapMethod" "Language.JVM.Attribute.BootstrapMethods" "jvm-binary-0.1.0-JJ8Rr7ERir79pQaBJvdiXV" False) (C1 * (MetaCons "BootstrapMethod" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "method") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (DeepRef MethodHandle High))) (S1 * (MetaSel (Just Symbol "arguments") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (SizedList16 (Ref JValue High))))))
type Rep (BootstrapMethod Low) Source # 
type Rep (BootstrapMethod Low) = D1 * (MetaData "BootstrapMethod" "Language.JVM.Attribute.BootstrapMethods" "jvm-binary-0.1.0-JJ8Rr7ERir79pQaBJvdiXV" False) (C1 * (MetaCons "BootstrapMethod" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "method") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (DeepRef MethodHandle Low))) (S1 * (MetaSel (Just Symbol "arguments") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (SizedList16 (Ref JValue Low))))))