| Copyright | (c) Christian Gram Kalhauge 2018 |
|---|---|
| License | MIT |
| Maintainer | kalhuage@cs.ucla.edu |
| Safe Haskell | Safe |
| Language | Haskell2010 |
Language.JVM.Type
Description
This module contains the JType, ClassName, MethodDescriptor, and
FieldDescriptor.
Synopsis
- newtype ClassName = ClassName {}
- strCls :: String -> ClassName
- dotCls :: Text -> ClassName
- data JType
- data JBaseType
- jBaseTypeToChar :: JBaseType -> Char
- data JRefType
- refTypeDepth :: JRefType -> Int
- data MethodDescriptor = MethodDescriptor {}
- newtype FieldDescriptor = FieldDescriptor {}
- data NameAndType a = NameAndType {
- ntName :: Text
- ntDescriptor :: a
- (<:>) :: Text -> a -> NameAndType a
- class TypeParse a where
- parseType :: Parser a
- typeToBuilder :: a -> Builder
- typeFromText :: TypeParse a => Text -> Either String a
- typeToText :: TypeParse a => a -> Text
- parseOnly :: Parser a -> Text -> Either String a
- parseFlatJRefType :: Parser JRefType
- jRefTypeToFlatText :: JRefType -> Text
Base types
ClassName
A class name
Constructors
| ClassName | |
Fields | |
Instances
| Eq ClassName Source # | |
| Ord ClassName Source # | |
| Show ClassName Source # | |
| IsString ClassName Source # | |
Defined in Language.JVM.Type Methods fromString :: String -> ClassName # | |
| Generic ClassName Source # | |
| NFData ClassName Source # | |
Defined in Language.JVM.Type | |
| TypeParse ClassName Source # | |
| Referenceable ClassName Source # | |
| type Rep ClassName Source # | |
Defined in Language.JVM.Type | |
strCls :: String -> ClassName Source #
Wrapper method that converts a string representation of a class into a class.
JType
Instances
| Eq JType Source # | |
| Ord JType Source # | |
| Show JType Source # | |
| IsString JType Source # | |
Defined in Language.JVM.Type Methods fromString :: String -> JType # | |
| Generic JType Source # | |
| NFData JType Source # | |
Defined in Language.JVM.Type | |
| TypeParse JType Source # | |
| type Rep JType Source # | |
Defined in Language.JVM.Type type Rep JType = D1 (MetaData "JType" "Language.JVM.Type" "jvm-binary-0.5.0-8tjUXfOvOFm5evlZ3bpMMl" False) (C1 (MetaCons "JTBase" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 JBaseType)) :+: C1 (MetaCons "JTRef" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 JRefType))) | |
The Jvm Primitive Types
Instances
| Eq JBaseType Source # | |
| Ord JBaseType Source # | |
| Show JBaseType Source # | |
| Generic JBaseType Source # | |
| NFData JBaseType Source # | |
Defined in Language.JVM.Type | |
| TypeParse JBaseType Source # | |
| type Rep JBaseType Source # | |
Defined in Language.JVM.Type type Rep JBaseType = D1 (MetaData "JBaseType" "Language.JVM.Type" "jvm-binary-0.5.0-8tjUXfOvOFm5evlZ3bpMMl" 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)))) | |
Instances
| Eq JRefType Source # | |
| Ord JRefType Source # | |
Defined in Language.JVM.Type | |
| Show JRefType Source # | |
| Generic JRefType Source # | |
| NFData JRefType Source # | |
Defined in Language.JVM.Type | |
| TypeParse JRefType Source # | |
| Referenceable JRefType Source # | |
| type Rep JRefType Source # | |
Defined in Language.JVM.Type type Rep JRefType = D1 (MetaData "JRefType" "Language.JVM.Type" "jvm-binary-0.5.0-8tjUXfOvOFm5evlZ3bpMMl" 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
Constructors
| MethodDescriptor | |
Fields | |
Instances
FieldDescriptor
newtype FieldDescriptor Source #
Field Descriptor
Constructors
| FieldDescriptor | |
Fields | |
Instances
NameAndType
data NameAndType a Source #
A name and a type
Constructors
| NameAndType | |
Fields
| |
Instances
(<:>) :: Text -> a -> NameAndType a Source #
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
Instances
| TypeParse FieldDescriptor Source # | |
Defined in Language.JVM.Type Methods | |
| TypeParse MethodDescriptor Source # | |
Defined in Language.JVM.Type Methods | |
| TypeParse JType Source # | |
| TypeParse JRefType Source # | |
| TypeParse JBaseType Source # | |
| TypeParse ClassName Source # | |
| TypeParse t => TypeParse (NameAndType t) Source # | |
Defined in Language.JVM.Type Methods parseType :: Parser (NameAndType t) Source # typeToBuilder :: NameAndType t -> Builder Source # | |
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)
jRefTypeToFlatText :: JRefType -> Text Source #