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

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

Language.JVM.Type

Contents

Description

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

Synopsis

Base types

ClassName

newtype ClassName Source #

A class name

Constructors

ClassName 
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 -> () #

TypeParse 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.8.0-HpvPbNkzsQo844TuM02sMI" True) (C1 (MetaCons "ClassName" PrefixI True) (S1 (MetaSel (Just "classNameAsText") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))

strCls :: String -> ClassName Source #

Wrapper method that converts a string representation of a class into a class.

dotCls :: Text -> ClassName Source #

Takes the dot representation and converts it into a class.

JType

data JType Source #

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 -> () #

TypeParse ReturnDescriptor Source # 
Instance details

Defined in Language.JVM.Type

TypeParse JType 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 JType Source # 
Instance details

Defined in Language.JVM.Type

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

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 -> () #

TypeParse 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.8.0-HpvPbNkzsQo844TuM02sMI" 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

data JRefType Source #

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

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 -> () #

TypeParse 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.8.0-HpvPbNkzsQo844TuM02sMI" 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

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 -> () #

TypeParse MethodDescriptor Source # 
Instance details

Defined in Language.JVM.Type

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.8.0-HpvPbNkzsQo844TuM02sMI" False) (C1 (MetaCons "MethodDescriptor" PrefixI True) (S1 (MetaSel (Just "methodDescriptorArguments") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [JType]) :*: S1 (MetaSel (Just "methodDescriptorReturnType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ReturnDescriptor)))

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 -> () #

TypeParse FieldDescriptor Source # 
Instance details

Defined in Language.JVM.Type

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.8.0-HpvPbNkzsQo844TuM02sMI" True) (C1 (MetaCons "FieldDescriptor" PrefixI True) (S1 (MetaSel (Just "fieldDescriptorType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 JType)))

NameAndType

data NameAndType a Source #

A name and a type

Constructors

NameAndType 

Fields

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

TypeParse t => IsString (NameAndType t) 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 -> () #

TypeParse t => TypeParse (NameAndType t) Source # 
Instance details

Defined in Language.JVM.Type

TypeParse 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.8.0-HpvPbNkzsQo844TuM02sMI" False) (C1 (MetaCons "NameAndType" PrefixI True) (S1 (MetaSel (Just "ntName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text) :*: S1 (MetaSel (Just "ntDescriptor") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))

TypeParse

class TypeParse a where Source #

Methods

parseType :: Parser a Source #

A TypeParse should be parsable

typeToBuilder :: a -> Builder Source #

A TypeParse should be printable

typeFromText :: TypeParse a => Text -> Either String a Source #

Parse a type from text

typeToText :: TypeParse a => a -> Text Source #

Convert a type into text

parseOnly :: Parser a -> Text -> Either String a #

Run a parser that cannot be resupplied via a Partial result.

This function does not force a parser to consume all of its input. Instead, any residual input will be discarded. To force a parser to consume all of its input, use something like this:

parseOnly (myParser <* endOfInput)