jvm-binary-0.10.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

Instances details
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.10.0-6UZh5809b0fJPIjalFrBq2" '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.10.0-6UZh5809b0fJPIjalFrBq2" 'True) (C1 ('MetaCons "BootstrapMethods" 'PrefixI 'True) (S1 ('MetaSel ('Just "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

Instances details
Staged BootstrapMethod Source # 
Instance details

Defined in Language.JVM.Attribute.BootstrapMethods

Methods

stage :: LabelM m => (forall (s' :: Type -> Type). 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 # 
Instance details

Defined in Language.JVM.Attribute.BootstrapMethods

Eq (BootstrapMethod Low) Source # 
Instance details

Defined in Language.JVM.Attribute.BootstrapMethods

Ord (BootstrapMethod Low) Source # 
Instance details

Defined in Language.JVM.Attribute.BootstrapMethods

Show (BootstrapMethod High) Source # 
Instance details

Defined in Language.JVM.Attribute.BootstrapMethods

Show (BootstrapMethod Low) Source # 
Instance details

Defined in Language.JVM.Attribute.BootstrapMethods

Generic (BootstrapMethod High) Source # 
Instance details

Defined in Language.JVM.Attribute.BootstrapMethods

Associated Types

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

Generic (BootstrapMethod Low) Source # 
Instance details

Defined in Language.JVM.Attribute.BootstrapMethods

Associated Types

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

Binary (BootstrapMethod Low) Source # 
Instance details

Defined in Language.JVM.Attribute.BootstrapMethods

NFData (BootstrapMethod High) Source # 
Instance details

Defined in Language.JVM.Attribute.BootstrapMethods

Methods

rnf :: BootstrapMethod High -> () #

NFData (BootstrapMethod Low) Source # 
Instance details

Defined in Language.JVM.Attribute.BootstrapMethods

Methods

rnf :: BootstrapMethod Low -> () #

type Rep (BootstrapMethod High) Source # 
Instance details

Defined in Language.JVM.Attribute.BootstrapMethods

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

Defined in Language.JVM.Attribute.BootstrapMethods

type Rep (BootstrapMethod Low) = D1 ('MetaData "BootstrapMethod" "Language.JVM.Attribute.BootstrapMethods" "jvm-binary-0.10.0-6UZh5809b0fJPIjalFrBq2" 'False) (C1 ('MetaCons "BootstrapMethod" 'PrefixI 'True) (S1 ('MetaSel ('Just "method") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (DeepRef MethodHandle Low)) :*: S1 ('MetaSel ('Just "arguments") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (SizedList16 (Ref JValue Low)))))