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.Field

Contents

Description

 

Synopsis

Documentation

data Field r Source #

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

Instances

Staged Field Source # 

Methods

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

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

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

Eq (Field High) Source # 

Methods

(==) :: Field High -> Field High -> Bool #

(/=) :: Field High -> Field High -> Bool #

Eq (Field Low) Source # 

Methods

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

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

Ord (Field Low) Source # 
Show (Field High) Source # 
Show (Field Low) Source # 
Generic (Field High) Source # 

Associated Types

type Rep (Field High) :: * -> * #

Methods

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

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

Generic (Field Low) Source # 

Associated Types

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

Methods

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

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

Binary (Field Low) Source # 

Methods

put :: Field Low -> Put #

get :: Get (Field Low) #

putList :: [Field Low] -> Put #

NFData (Field High) Source # 

Methods

rnf :: Field High -> () #

NFData (Field Low) Source # 

Methods

rnf :: Field Low -> () #

type Rep (Field High) Source # 
type Rep (Field Low) Source # 

fAccessFlags :: Field r -> Set FAccessFlag Source #

Get the set of access flags

Attributes

fSignature :: Field High -> Maybe (Signature High) Source #

Fetches the Signature attribute, if any.

data FieldAttributes r Source #

Instances

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

Associated Types

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

NFData (FieldAttributes High) Source # 

Methods

rnf :: FieldAttributes High -> () #

NFData (FieldAttributes Low) Source # 

Methods

rnf :: FieldAttributes Low -> () #

type Rep (FieldAttributes High) Source # 
type Rep (FieldAttributes High) = D1 * (MetaData "FieldAttributes" "Language.JVM.Field" "jvm-binary-0.1.0-JJ8Rr7ERir79pQaBJvdiXV" False) (C1 * (MetaCons "FieldAttributes" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "faConstantValues") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [ConstantValue High])) ((:*:) * (S1 * (MetaSel (Just Symbol "faSignatures") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [Signature High])) (S1 * (MetaSel (Just Symbol "faOthers") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [Attribute High])))))
type Rep (FieldAttributes Low) Source # 
type Rep (FieldAttributes Low) = D1 * (MetaData "FieldAttributes" "Language.JVM.Field" "jvm-binary-0.1.0-JJ8Rr7ERir79pQaBJvdiXV" False) (C1 * (MetaCons "FieldAttributes" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "faConstantValues") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [ConstantValue Low])) ((:*:) * (S1 * (MetaSel (Just Symbol "faSignatures") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [Signature Low])) (S1 * (MetaSel (Just Symbol "faOthers") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [Attribute Low])))))