Copyright | (c) Christian Gram Kalhauge 2018 |
---|---|
License | MIT |
Maintainer | kalhuage@cs.ucla.edu |
Safe Haskell | None |
Language | Haskell2010 |
Synopsis
- class Staged s where
- class Monad m => LabelM m where
- class LabelM m => EvolveM m where
- link :: Referenceable r => Index -> m r
- attributeFilter :: m ((AttributeLocation, Text) -> Bool)
- evolveError :: String -> m r
- class LabelM m => DevolveM m where
- unlink :: Referenceable r => r -> m Index
- data AttributeLocation
- module Language.JVM.Stage
- module Language.JVM.TH
Documentation
stage :: LabelM m => (forall s'. Staged s' => s' r -> m (s' r')) -> s r -> m (s r') Source #
Instances
Monad Classes
class Monad m => LabelM m where Source #
Nothing
label :: String -> m a -> m a Source #
label the current position in the class-file, good for debugging
Instances
LabelM ConstantPoolBuilder Source # | |
Defined in Language.JVM.ClassFileReader label :: String -> ConstantPoolBuilder a -> ConstantPoolBuilder a Source # | |
LabelM Evolve Source # | |
class LabelM m => EvolveM m where Source #
link :: Referenceable r => Index -> m r Source #
attributeFilter :: m ((AttributeLocation, Text) -> Bool) Source #
evolveError :: String -> m r Source #
Instances
EvolveM Evolve Source # | |
Defined in Language.JVM.ClassFileReader link :: Referenceable r => Index -> Evolve r Source # attributeFilter :: Evolve ((AttributeLocation, Text) -> Bool) Source # evolveError :: String -> Evolve r Source # |
class LabelM m => DevolveM m where Source #
unlink :: Referenceable r => r -> m Index Source #
Instances
DevolveM ConstantPoolBuilder Source # | |
Defined in Language.JVM.ClassFileReader unlink :: Referenceable r => r -> ConstantPoolBuilder Index Source # |
AttributeLocation
data AttributeLocation Source #
Instances
Eq AttributeLocation Source # | |
Defined in Language.JVM.Staged (==) :: AttributeLocation -> AttributeLocation -> Bool # (/=) :: AttributeLocation -> AttributeLocation -> Bool # | |
Ord AttributeLocation Source # | |
Defined in Language.JVM.Staged compare :: AttributeLocation -> AttributeLocation -> Ordering # (<) :: AttributeLocation -> AttributeLocation -> Bool # (<=) :: AttributeLocation -> AttributeLocation -> Bool # (>) :: AttributeLocation -> AttributeLocation -> Bool # (>=) :: AttributeLocation -> AttributeLocation -> Bool # max :: AttributeLocation -> AttributeLocation -> AttributeLocation # min :: AttributeLocation -> AttributeLocation -> AttributeLocation # | |
Show AttributeLocation Source # | |
Defined in Language.JVM.Staged showsPrec :: Int -> AttributeLocation -> ShowS # show :: AttributeLocation -> String # showList :: [AttributeLocation] -> ShowS # |
Re-exports
module Language.JVM.Stage
module Language.JVM.TH