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

Contents

Description

 

Synopsis

Documentation

data Attribute r Source #

An Attribute, simply contains of a reference to a name and contains info.

Constructors

Attribute 

Fields

Instances

Staged Attribute Source # 

Methods

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

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

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

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

Associated Types

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

Generic (Attribute Low) Source # 

Associated Types

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

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

Methods

rnf :: Attribute High -> () #

NFData (Attribute Low) Source # 

Methods

rnf :: Attribute Low -> () #

type Rep (Attribute High) Source # 
type Rep (Attribute High) = D1 * (MetaData "Attribute" "Language.JVM.Attribute.Base" "jvm-binary-0.1.0-JJ8Rr7ERir79pQaBJvdiXV" False) (C1 * (MetaCons "Attribute" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "aName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Ref Text High))) (S1 * (MetaSel (Just Symbol "aInfo'") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * SizedByteString32))))
type Rep (Attribute Low) Source # 
type Rep (Attribute Low) = D1 * (MetaData "Attribute" "Language.JVM.Attribute.Base" "jvm-binary-0.1.0-JJ8Rr7ERir79pQaBJvdiXV" False) (C1 * (MetaCons "Attribute" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "aName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Ref Text Low))) (S1 * (MetaSel (Just Symbol "aInfo'") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * SizedByteString32))))

aInfo :: Attribute r -> ByteString Source #

A small helper function to extract the info as a lazy ByteString.

devolveAttribute :: (IsAttribute (a Low), DevolveM m) => (a High -> m (a Low)) -> a High -> m (Attribute Low) Source #

fromAttribute' :: IsAttribute a => Attribute r -> Either String a Source #

Generate an attribute in a low stage Low.

Helpers

class Binary a => IsAttribute a where Source #

A class-type that describes a data-type a as an Attribute. Most notable it provides the fromAttribute' method that enables converting an Attribute to a data-type a.

Minimal complete definition

attrName

Methods

attrName :: Const Text a Source #

The name of an attribute. This is used to lookup an attribute.

type Attributes b r = Choice (SizedList16 (Attribute r)) (b r) r Source #

A list of attributes and described by the expected values.

fromAttributes :: (Foldable f, EvolveM m, Monoid a) => (Attribute High -> m a) -> f (Attribute Low) -> m a Source #

Given a Foldable structure f, and a function that can calculate a monoid given an Attribute calculate the monoid over all attributes.

toC :: (EvolveM m, Staged a, IsAttribute (a Low)) => (a High -> c) -> Attribute High -> Maybe (m c) Source #

toC' :: (EvolveM m, IsAttribute (a Low)) => (a Low -> m (a High)) -> (a High -> c) -> Attribute High -> Maybe (m c) Source #

collect :: Monad m => c -> Attribute High -> [Attribute High -> Maybe (m c)] -> m c Source #

newtype Const a b Source #

Create a type dependent on another type b, used for accessing the correct attrName in IsAttribute.

Constructors

Const 

Fields

firstOne :: [a] -> Maybe a Source #

Maybe return the first element of a list