jvm-binary-0.9.0: A library for reading Java class-files

Copyright(c) Christian Gram Kalhauge 2018
LicenseMIT
Maintainerkalhuage@cs.ucla.edu
Safe HaskellNone
LanguageHaskell2010

Language.JVM.Type

Contents

Description

This module contains the JType, ClassName, MethodDescriptor, and FieldDescriptor.

Synopsis

Base types

ClassName

data ClassName Source #

A class name

Instances
Eq ClassName Source # 
Instance details

Defined in Language.JVM.Type

Ord ClassName Source # 
Instance details

Defined in Language.JVM.Type

Show ClassName Source # 
Instance details

Defined in Language.JVM.Type

IsString ClassName Source # 
Instance details

Defined in Language.JVM.Type

Generic ClassName Source # 
Instance details

Defined in Language.JVM.Type

Associated Types

type Rep ClassName :: Type -> Type #

NFData ClassName Source # 
Instance details

Defined in Language.JVM.Type

Methods

rnf :: ClassName -> () #

TextSerializable ClassName Source # 
Instance details

Defined in Language.JVM.Type

Referenceable ClassName Source # 
Instance details

Defined in Language.JVM.Constant

Methods

fromConst :: Monad m => (forall a'. String -> m a') -> Constant High -> m ClassName Source #

toConst :: Monad m => ClassName -> m (Constant High) Source #

type Rep ClassName Source # 
Instance details

Defined in Language.JVM.Type

type Rep ClassName = D1 (MetaData "ClassName" "Language.JVM.Type" "jvm-binary-0.9.0-9S1OjG3yP2JAIJl8zf6L4B" True) (C1 (MetaCons "ClassName" PrefixI True) (S1 (MetaSel (Just "classNameAsText") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))

textCls :: Text -> Either String ClassName Source #

Parses a ClassName from Text, might fail.

textClsOrFail :: Text -> ClassName Source #

Parses a ClassName from String, might fail with an exception. *warning* Unpure.

strClsOrFail :: String -> ClassName Source #

Parses a ClassName from String, might fail with an exception. *warning* Unpure.

dotCls :: Text -> Either String ClassName Source #

Takes the dot representation and converts it into a class.

unsafeTextCls :: Text -> ClassName Source #

Converts a text directly into a ClassName, will fail silently and might corrupt data.

parseClassName :: Parser ClassName Source #

Parse a ClassName, should not be any of '.;[<>:',

>>> deserialize parseClassName "java/lang/Object"
Right "java/lang/Object"
>>> deserialize parseClassName "java;"
Left "endOfInput"

serializeClassName :: ClassName -> Builder Source #

Display a ClassName

JType

data JType Source #

A JType is either a simple type or a Reftype

Constructors

JTBase !JBaseType 
JTRef !JRefType 
Instances
Eq JType Source # 
Instance details

Defined in Language.JVM.Type

Methods

(==) :: JType -> JType -> Bool #

(/=) :: JType -> JType -> Bool #

Ord JType Source # 
Instance details

Defined in Language.JVM.Type

Methods

compare :: JType -> JType -> Ordering #

(<) :: JType -> JType -> Bool #

(<=) :: JType -> JType -> Bool #

(>) :: JType -> JType -> Bool #

(>=) :: JType -> JType -> Bool #

max :: JType -> JType -> JType #

min :: JType -> JType -> JType #

Show JType Source # 
Instance details

Defined in Language.JVM.Type

Methods

showsPrec :: Int -> JType -> ShowS #

show :: JType -> String #

showList :: [JType] -> ShowS #

IsString JType Source # 
Instance details

Defined in Language.JVM.Type

Methods

fromString :: String -> JType #

Generic JType Source # 
Instance details

Defined in Language.JVM.Type

Associated Types

type Rep JType :: Type -> Type #

Methods

from :: JType -> Rep JType x #

to :: Rep JType x -> JType #

NFData JType Source # 
Instance details

Defined in Language.JVM.Type

Methods

rnf :: JType -> () #

TextSerializable JType Source # 
Instance details

Defined in Language.JVM.Type

type Rep JType Source # 
Instance details

Defined in Language.JVM.Type

jTypeSize :: JType -> Int Source #

jTypes also have different sizes.

parseJType :: Parser JType Source #

Parse a JType

data JBaseType Source #

The Jvm Primitive Types

Instances
Eq JBaseType Source # 
Instance details

Defined in Language.JVM.Type

Ord JBaseType Source # 
Instance details

Defined in Language.JVM.Type

Show JBaseType Source # 
Instance details

Defined in Language.JVM.Type

IsString JBaseType Source # 
Instance details

Defined in Language.JVM.Type

Generic JBaseType Source # 
Instance details

Defined in Language.JVM.Type

Associated Types

type Rep JBaseType :: Type -> Type #

NFData JBaseType Source # 
Instance details

Defined in Language.JVM.Type

Methods

rnf :: JBaseType -> () #

TextSerializable JBaseType Source # 
Instance details

Defined in Language.JVM.Type

type Rep JBaseType Source # 
Instance details

Defined in Language.JVM.Type

type Rep JBaseType = D1 (MetaData "JBaseType" "Language.JVM.Type" "jvm-binary-0.9.0-9S1OjG3yP2JAIJl8zf6L4B" False) (((C1 (MetaCons "JTByte" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "JTChar" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "JTDouble" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "JTFloat" PrefixI False) (U1 :: Type -> Type))) :+: ((C1 (MetaCons "JTInt" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "JTLong" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "JTShort" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "JTBoolean" PrefixI False) (U1 :: Type -> Type))))

jBaseTypeToChar :: JBaseType -> Char Source #

Get the corresponding Char of a JBaseType

jBaseTypeSize :: JBaseType -> Int Source #

Doubles and Longs have size two in the stack.

parseJBaseType :: Parser JBaseType Source #

Parse a JBaseType

serializeJBaseType :: JBaseType -> Builder Source #

Serializes JBaseType

data JRefType Source #

A JRefType is a Class or an Array.

Constructors

JTClass !ClassName 
JTArray !JType 
Instances
Eq JRefType Source # 
Instance details

Defined in Language.JVM.Type

Ord JRefType Source # 
Instance details

Defined in Language.JVM.Type

Show JRefType Source # 
Instance details

Defined in Language.JVM.Type

IsString JRefType Source # 
Instance details

Defined in Language.JVM.Type

Generic JRefType Source # 
Instance details

Defined in Language.JVM.Type

Associated Types

type Rep JRefType :: Type -> Type #

Methods

from :: JRefType -> Rep JRefType x #

to :: Rep JRefType x -> JRefType #

NFData JRefType Source # 
Instance details

Defined in Language.JVM.Type

Methods

rnf :: JRefType -> () #

TextSerializable JRefType Source # 
Instance details

Defined in Language.JVM.Type

Referenceable JRefType Source # 
Instance details

Defined in Language.JVM.Constant

Methods

fromConst :: Monad m => (forall a'. String -> m a') -> Constant High -> m JRefType Source #

toConst :: Monad m => JRefType -> m (Constant High) Source #

type Rep JRefType Source # 
Instance details

Defined in Language.JVM.Type

type Rep JRefType = D1 (MetaData "JRefType" "Language.JVM.Type" "jvm-binary-0.9.0-9S1OjG3yP2JAIJl8zf6L4B" False) (C1 (MetaCons "JTClass" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 ClassName)) :+: C1 (MetaCons "JTArray" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 JType)))

refTypeDepth :: JRefType -> Int Source #

The number of nested arrays

parseFlatJRefType :: Parser JRefType Source #

Parses a JRefType but does not require an L infront of the class name, and ';' >>> deserialize parseFlatJRefType "javalangObject" Right "LjavalangObject;" >>> deserialize parseFlatJRefType "[I" Right "[I"

MethodDescriptor

data MethodDescriptor Source #

Method Descriptor

Instances
Eq MethodDescriptor Source # 
Instance details

Defined in Language.JVM.Type

Ord MethodDescriptor Source # 
Instance details

Defined in Language.JVM.Type

Show MethodDescriptor Source # 
Instance details

Defined in Language.JVM.Type

IsString MethodDescriptor Source # 
Instance details

Defined in Language.JVM.Type

Generic MethodDescriptor Source # 
Instance details

Defined in Language.JVM.Type

Associated Types

type Rep MethodDescriptor :: Type -> Type #

NFData MethodDescriptor Source # 
Instance details

Defined in Language.JVM.Type

Methods

rnf :: MethodDescriptor -> () #

TextSerializable MethodDescriptor Source # 
Instance details

Defined in Language.JVM.Type

WithName MethodDescriptor Source # 
Instance details

Defined in Language.JVM.Type

Associated Types

type WithNameId MethodDescriptor :: Type Source #

Referenceable MethodDescriptor Source # 
Instance details

Defined in Language.JVM.Constant

Methods

fromConst :: Monad m => (forall a'. String -> m a') -> Constant High -> m MethodDescriptor Source #

toConst :: Monad m => MethodDescriptor -> m (Constant High) Source #

type Rep MethodDescriptor Source # 
Instance details

Defined in Language.JVM.Type

type Rep MethodDescriptor = D1 (MetaData "MethodDescriptor" "Language.JVM.Type" "jvm-binary-0.9.0-9S1OjG3yP2JAIJl8zf6L4B" False) (C1 (MetaCons "MethodDescriptor" PrefixI True) (S1 (MetaSel (Just "methodDescriptorArguments") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 [JType]) :*: S1 (MetaSel (Just "methodDescriptorReturnType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 ReturnDescriptor)))
type WithNameId MethodDescriptor Source # 
Instance details

Defined in Language.JVM.Type

parseMethodDescriptor :: Parser MethodDescriptor Source #

A MethodDescriptor is just a list of types

>>> deserialize parseMethodDescriptor "(II)V"
Right "(II)V"

newtype ReturnDescriptor Source #

A ReturnDescriptor is maybe a type, otherwise it is void. https://docs.oracle.com/javase/specs/jvms/se8/html/jvms-4.html#jvms-4.3.3

Constructors

ReturnDescriptor 
Instances
Eq ReturnDescriptor Source # 
Instance details

Defined in Language.JVM.Type

Ord ReturnDescriptor Source # 
Instance details

Defined in Language.JVM.Type

Show ReturnDescriptor Source # 
Instance details

Defined in Language.JVM.Type

IsString ReturnDescriptor Source # 
Instance details

Defined in Language.JVM.Type

Generic ReturnDescriptor Source # 
Instance details

Defined in Language.JVM.Type

Associated Types

type Rep ReturnDescriptor :: Type -> Type #

NFData ReturnDescriptor Source # 
Instance details

Defined in Language.JVM.Type

Methods

rnf :: ReturnDescriptor -> () #

TextSerializable ReturnDescriptor Source # 
Instance details

Defined in Language.JVM.Type

Referenceable ReturnDescriptor Source # 
Instance details

Defined in Language.JVM.Constant

Methods

fromConst :: Monad m => (forall a'. String -> m a') -> Constant High -> m ReturnDescriptor Source #

toConst :: Monad m => ReturnDescriptor -> m (Constant High) Source #

type Rep ReturnDescriptor Source # 
Instance details

Defined in Language.JVM.Type

type Rep ReturnDescriptor = D1 (MetaData "ReturnDescriptor" "Language.JVM.Type" "jvm-binary-0.9.0-9S1OjG3yP2JAIJl8zf6L4B" True) (C1 (MetaCons "ReturnDescriptor" PrefixI True) (S1 (MetaSel (Just "asMaybeJType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe JType))))

parseReturnDescriptor :: Parser ReturnDescriptor Source #

A ReturnDescriptor is either A JType or A void V annotaiton:

>>> deserialize parseReturnDescriptor "V"
Right Nothing
>>> parseTest parseReturnDescriptor "[I"
Right (Just "[I")

FieldDescriptor

newtype FieldDescriptor Source #

Field Descriptor

Constructors

FieldDescriptor 
Instances
Eq FieldDescriptor Source # 
Instance details

Defined in Language.JVM.Type

Ord FieldDescriptor Source # 
Instance details

Defined in Language.JVM.Type

Show FieldDescriptor Source # 
Instance details

Defined in Language.JVM.Type

IsString FieldDescriptor Source # 
Instance details

Defined in Language.JVM.Type

Generic FieldDescriptor Source # 
Instance details

Defined in Language.JVM.Type

Associated Types

type Rep FieldDescriptor :: Type -> Type #

NFData FieldDescriptor Source # 
Instance details

Defined in Language.JVM.Type

Methods

rnf :: FieldDescriptor -> () #

TextSerializable FieldDescriptor Source # 
Instance details

Defined in Language.JVM.Type

WithName FieldDescriptor Source # 
Instance details

Defined in Language.JVM.Type

Associated Types

type WithNameId FieldDescriptor :: Type Source #

Referenceable FieldDescriptor Source # 
Instance details

Defined in Language.JVM.Constant

Methods

fromConst :: Monad m => (forall a'. String -> m a') -> Constant High -> m FieldDescriptor Source #

toConst :: Monad m => FieldDescriptor -> m (Constant High) Source #

type Rep FieldDescriptor Source # 
Instance details

Defined in Language.JVM.Type

type Rep FieldDescriptor = D1 (MetaData "FieldDescriptor" "Language.JVM.Type" "jvm-binary-0.9.0-9S1OjG3yP2JAIJl8zf6L4B" True) (C1 (MetaCons "FieldDescriptor" PrefixI True) (S1 (MetaSel (Just "fieldDescriptorType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 JType)))
type WithNameId FieldDescriptor Source # 
Instance details

Defined in Language.JVM.Type

parseFieldDescriptor :: Parser FieldDescriptor Source #

A FieldDescriptor is just a JType

>>> deserialize parseMethodDescriptor "I"
Right "I"

NameAndType

data NameAndType a Source #

A name and a type

Constructors

NameAndType !Text !a 
Instances
Eq a => Eq (NameAndType a) Source # 
Instance details

Defined in Language.JVM.Type

Ord a => Ord (NameAndType a) Source # 
Instance details

Defined in Language.JVM.Type

Show a => Show (NameAndType a) Source # 
Instance details

Defined in Language.JVM.Type

Generic (NameAndType a) Source # 
Instance details

Defined in Language.JVM.Type

Associated Types

type Rep (NameAndType a) :: Type -> Type #

Methods

from :: NameAndType a -> Rep (NameAndType a) x #

to :: Rep (NameAndType a) x -> NameAndType a #

NFData a => NFData (NameAndType a) Source # 
Instance details

Defined in Language.JVM.Type

Methods

rnf :: NameAndType a -> () #

AsNameAndType (NameAndType a) Source # 
Instance details

Defined in Language.JVM.Type

Associated Types

type TypeDescriptor (NameAndType a) :: Type Source #

TextSerializable a => Referenceable (NameAndType a) Source # 
Instance details

Defined in Language.JVM.Constant

Methods

fromConst :: Monad m => (forall a'. String -> m a') -> Constant High -> m (NameAndType a) Source #

toConst :: Monad m => NameAndType a -> m (Constant High) Source #

type Rep (NameAndType a) Source # 
Instance details

Defined in Language.JVM.Type

type Rep (NameAndType a) = D1 (MetaData "NameAndType" "Language.JVM.Type" "jvm-binary-0.9.0-9S1OjG3yP2JAIJl8zf6L4B" False) (C1 (MetaCons "NameAndType" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 a)))
type TypeDescriptor (NameAndType a) Source # 
Instance details

Defined in Language.JVM.Type

parseNameAndType :: Parser a -> Parser (NameAndType a) Source #

A FieldDescriptor is just a JType

>>> deserialize (parseNameAndType parseMethodDescriptor) "method:(I)V"
Right "method:(I)V"

class WithName n where Source #

Associated Types

type WithNameId n Source #

Methods

(<:>) :: Text -> n -> WithNameId n Source #

MethodId

newtype MethodId Source #

A MethodId

Instances
Eq MethodId Source # 
Instance details

Defined in Language.JVM.Type

Ord MethodId Source # 
Instance details

Defined in Language.JVM.Type

Show MethodId Source # 
Instance details

Defined in Language.JVM.Type

IsString MethodId Source # 
Instance details

Defined in Language.JVM.Type

Generic MethodId Source # 
Instance details

Defined in Language.JVM.Type

Associated Types

type Rep MethodId :: Type -> Type #

Methods

from :: MethodId -> Rep MethodId x #

to :: Rep MethodId x -> MethodId #

NFData MethodId Source # 
Instance details

Defined in Language.JVM.Type

Methods

rnf :: MethodId -> () #

TextSerializable MethodId Source # 
Instance details

Defined in Language.JVM.Type

AsNameAndType MethodId Source # 
Instance details

Defined in Language.JVM.Type

Associated Types

type TypeDescriptor MethodId :: Type Source #

Referenceable MethodId Source # 
Instance details

Defined in Language.JVM.Constant

Methods

fromConst :: Monad m => (forall a'. String -> m a') -> Constant High -> m MethodId Source #

toConst :: Monad m => MethodId -> m (Constant High) Source #

Referenceable (InRefType MethodId) Source # 
Instance details

Defined in Language.JVM.Constant

Methods

fromConst :: Monad m => (forall a'. String -> m a') -> Constant High -> m (InRefType MethodId) Source #

toConst :: Monad m => InRefType MethodId -> m (Constant High) Source #

type Rep MethodId Source # 
Instance details

Defined in Language.JVM.Type

type Rep MethodId = D1 (MetaData "MethodId" "Language.JVM.Type" "jvm-binary-0.9.0-9S1OjG3yP2JAIJl8zf6L4B" True) (C1 (MetaCons "MethodId" PrefixI True) (S1 (MetaSel (Just "methodIdAsNameAndType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (NameAndType MethodDescriptor))))
type TypeDescriptor MethodId Source # 
Instance details

Defined in Language.JVM.Type

FieldId

newtype FieldId Source #

A FieldId

Instances
Eq FieldId Source # 
Instance details

Defined in Language.JVM.Type

Methods

(==) :: FieldId -> FieldId -> Bool #

(/=) :: FieldId -> FieldId -> Bool #

Ord FieldId Source # 
Instance details

Defined in Language.JVM.Type

Show FieldId Source # 
Instance details

Defined in Language.JVM.Type

IsString FieldId Source # 
Instance details

Defined in Language.JVM.Type

Methods

fromString :: String -> FieldId #

Generic FieldId Source # 
Instance details

Defined in Language.JVM.Type

Associated Types

type Rep FieldId :: Type -> Type #

Methods

from :: FieldId -> Rep FieldId x #

to :: Rep FieldId x -> FieldId #

NFData FieldId Source # 
Instance details

Defined in Language.JVM.Type

Methods

rnf :: FieldId -> () #

TextSerializable FieldId Source # 
Instance details

Defined in Language.JVM.Type

AsNameAndType FieldId Source # 
Instance details

Defined in Language.JVM.Type

Associated Types

type TypeDescriptor FieldId :: Type Source #

Referenceable FieldId Source # 
Instance details

Defined in Language.JVM.Constant

Methods

fromConst :: Monad m => (forall a'. String -> m a') -> Constant High -> m FieldId Source #

toConst :: Monad m => FieldId -> m (Constant High) Source #

type Rep FieldId Source # 
Instance details

Defined in Language.JVM.Type

type Rep FieldId = D1 (MetaData "FieldId" "Language.JVM.Type" "jvm-binary-0.9.0-9S1OjG3yP2JAIJl8zf6L4B" True) (C1 (MetaCons "FieldId" PrefixI True) (S1 (MetaSel (Just "fieldIdAsNameAndType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (NameAndType FieldDescriptor))))
type TypeDescriptor FieldId Source # 
Instance details

Defined in Language.JVM.Type

InClass

data InClass a Source #

A method or Field in a Class

Constructors

InClass 

Fields

Instances
Eq a => Eq (InClass a) Source # 
Instance details

Defined in Language.JVM.Type

Methods

(==) :: InClass a -> InClass a -> Bool #

(/=) :: InClass a -> InClass a -> Bool #

Ord a => Ord (InClass a) Source # 
Instance details

Defined in Language.JVM.Type

Methods

compare :: InClass a -> InClass a -> Ordering #

(<) :: InClass a -> InClass a -> Bool #

(<=) :: InClass a -> InClass a -> Bool #

(>) :: InClass a -> InClass a -> Bool #

(>=) :: InClass a -> InClass a -> Bool #

max :: InClass a -> InClass a -> InClass a #

min :: InClass a -> InClass a -> InClass a #

Show a => Show (InClass a) Source # 
Instance details

Defined in Language.JVM.Type

Methods

showsPrec :: Int -> InClass a -> ShowS #

show :: InClass a -> String #

showList :: [InClass a] -> ShowS #

Generic (InClass a) Source # 
Instance details

Defined in Language.JVM.Type

Associated Types

type Rep (InClass a) :: Type -> Type #

Methods

from :: InClass a -> Rep (InClass a) x #

to :: Rep (InClass a) x -> InClass a #

NFData a => NFData (InClass a) Source # 
Instance details

Defined in Language.JVM.Type

Methods

rnf :: InClass a -> () #

type Rep (InClass a) Source # 
Instance details

Defined in Language.JVM.Type

type Rep (InClass a) = D1 (MetaData "InClass" "Language.JVM.Type" "jvm-binary-0.9.0-9S1OjG3yP2JAIJl8zf6L4B" False) (C1 (MetaCons "InClass" PrefixI True) (S1 (MetaSel (Just "inClassName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 ClassName) :*: S1 (MetaSel (Just "inClassId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 a)))

InRefType

data InRefType a Source #

A method or Field in a Class

Constructors

InRefType 

Fields

Instances
Eq a => Eq (InRefType a) Source # 
Instance details

Defined in Language.JVM.Type

Methods

(==) :: InRefType a -> InRefType a -> Bool #

(/=) :: InRefType a -> InRefType a -> Bool #

Ord a => Ord (InRefType a) Source # 
Instance details

Defined in Language.JVM.Type

Show a => Show (InRefType a) Source # 
Instance details

Defined in Language.JVM.Type

Generic (InRefType a) Source # 
Instance details

Defined in Language.JVM.Type

Associated Types

type Rep (InRefType a) :: Type -> Type #

Methods

from :: InRefType a -> Rep (InRefType a) x #

to :: Rep (InRefType a) x -> InRefType a #

NFData a => NFData (InRefType a) Source # 
Instance details

Defined in Language.JVM.Type

Methods

rnf :: InRefType a -> () #

Referenceable (InRefType MethodId) Source # 
Instance details

Defined in Language.JVM.Constant

Methods

fromConst :: Monad m => (forall a'. String -> m a') -> Constant High -> m (InRefType MethodId) Source #

toConst :: Monad m => InRefType MethodId -> m (Constant High) Source #

type Rep (InRefType a) Source # 
Instance details

Defined in Language.JVM.Type

type Rep (InRefType a) = D1 (MetaData "InRefType" "Language.JVM.Type" "jvm-binary-0.9.0-9S1OjG3yP2JAIJl8zf6L4B" False) (C1 (MetaCons "InRefType" PrefixI True) (S1 (MetaSel (Just "inRefType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 JRefType) :*: S1 (MetaSel (Just "inRefTypeId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 a)))

inRefTypeAsInClass :: InRefType a -> InClass a Source #

Convert a InRefType to a InClass by casting all arrays to classes.

AbsMethodId

newtype AbsMethodId Source #

A MethodId

Instances
Eq AbsMethodId Source # 
Instance details

Defined in Language.JVM.Type

Ord AbsMethodId Source # 
Instance details

Defined in Language.JVM.Type

Show AbsMethodId Source # 
Instance details

Defined in Language.JVM.Type

IsString AbsMethodId Source # 
Instance details

Defined in Language.JVM.Type

Generic AbsMethodId Source # 
Instance details

Defined in Language.JVM.Type

Associated Types

type Rep AbsMethodId :: Type -> Type #

NFData AbsMethodId Source # 
Instance details

Defined in Language.JVM.Type

Methods

rnf :: AbsMethodId -> () #

TextSerializable AbsMethodId Source # 
Instance details

Defined in Language.JVM.Type

type Rep AbsMethodId Source # 
Instance details

Defined in Language.JVM.Type

type Rep AbsMethodId = D1 (MetaData "AbsMethodId" "Language.JVM.Type" "jvm-binary-0.9.0-9S1OjG3yP2JAIJl8zf6L4B" True) (C1 (MetaCons "AbsMethodId" PrefixI True) (S1 (MetaSel (Just "absMethodAsInClass") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (InClass MethodId))))

AbsFieldId

newtype AbsFieldId Source #

A FieldId

Instances
Eq AbsFieldId Source # 
Instance details

Defined in Language.JVM.Type

Ord AbsFieldId Source # 
Instance details

Defined in Language.JVM.Type

Show AbsFieldId Source # 
Instance details

Defined in Language.JVM.Type

IsString AbsFieldId Source # 
Instance details

Defined in Language.JVM.Type

Generic AbsFieldId Source # 
Instance details

Defined in Language.JVM.Type

Associated Types

type Rep AbsFieldId :: Type -> Type #

NFData AbsFieldId Source # 
Instance details

Defined in Language.JVM.Type

Methods

rnf :: AbsFieldId -> () #

TextSerializable AbsFieldId Source # 
Instance details

Defined in Language.JVM.Type

Referenceable AbsFieldId Source # 
Instance details

Defined in Language.JVM.Constant

Methods

fromConst :: Monad m => (forall a'. String -> m a') -> Constant High -> m AbsFieldId Source #

toConst :: Monad m => AbsFieldId -> m (Constant High) Source #

type Rep AbsFieldId Source # 
Instance details

Defined in Language.JVM.Type

type Rep AbsFieldId = D1 (MetaData "AbsFieldId" "Language.JVM.Type" "jvm-binary-0.9.0-9S1OjG3yP2JAIJl8zf6L4B" True) (C1 (MetaCons "AbsFieldId" PrefixI True) (S1 (MetaSel (Just "absFieldAsInClass") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (InClass FieldId))))

Re-export