Copyright | (c) Christian Gram Kalhauge 2018 |
---|---|
License | MIT |
Maintainer | kalhuage@cs.ucla.edu |
Safe Haskell | None |
Language | Haskell2010 |
Synopsis
- newtype Signature a = Signature (Ref Text a)
- signatureToText :: Signature High -> Text
- signatureFromText :: Text -> Signature High
- data ClassSignature = ClassSignature {}
- classSignatureToText :: ClassSignature -> Text
- classSignatureFromText :: Text -> Either String ClassSignature
- classSignatureP :: Parser ClassSignature
- data MethodSignature = MethodSignature {}
- methodSignatureToText :: MethodSignature -> Text
- methodSignatureFromText :: Text -> Either String MethodSignature
- methodSignatureP :: Parser MethodSignature
- newtype FieldSignature = FieldSignature {}
- fieldSignatureToText :: FieldSignature -> Text
- fieldSignatureFromText :: Text -> Either String FieldSignature
- fieldSignatureP :: Parser FieldSignature
- data ClassType
- = ClassType { }
- | InnerClassType { }
- classTypeP :: Parser ClassType
- data ReferenceType
- referenceTypeP :: Parser ReferenceType
- data ThrowsSignature
- data TypeArgument = TypeArgument {}
- data TypeParameter = TypeParameter {}
- data TypeSignature
- newtype TypeVariable = TypeVariable {}
- typeVariableP :: Parser TypeVariable
- data Wildcard
- typeParameterP :: Parser TypeParameter
- typeParametersP :: Parser [TypeParameter]
Documentation
Instances
Staged Signature Source # | |
Defined in Language.JVM.Attribute.Signature | |
Eq (Signature High) Source # | |
Eq (Signature Low) Source # | |
Ord (Signature Low) Source # | |
Defined in Language.JVM.Attribute.Signature compare :: Signature Low -> Signature Low -> Ordering # (<) :: Signature Low -> Signature Low -> Bool # (<=) :: Signature Low -> Signature Low -> Bool # (>) :: Signature Low -> Signature Low -> Bool # (>=) :: Signature Low -> Signature Low -> Bool # | |
Show (Signature High) Source # | |
Show (Signature Low) Source # | |
Generic (Signature High) Source # | |
Generic (Signature Low) Source # | |
Binary (Signature Low) Source # | |
NFData (Signature High) Source # | |
Defined in Language.JVM.Attribute.Signature | |
NFData (Signature Low) Source # | |
Defined in Language.JVM.Attribute.Signature | |
IsAttribute (Signature Low) Source # | |
type Rep (Signature High) Source # | |
Defined in Language.JVM.Attribute.Signature | |
type Rep (Signature Low) Source # | |
Defined in Language.JVM.Attribute.Signature |
Top Level Definitions
data ClassSignature Source #
Instances
data MethodSignature Source #
MethodSignature | |
|
Instances
newtype FieldSignature Source #
Instances
Lower Level Definitions
Instances
data ReferenceType Source #
Instances
data ThrowsSignature Source #
Instances
data TypeArgument Source #
Instances
data TypeParameter Source #
Instances
data TypeSignature Source #
Instances
newtype TypeVariable Source #
Instances
Eq TypeVariable Source # | |
Defined in Language.JVM.Attribute.Signature (==) :: TypeVariable -> TypeVariable -> Bool # (/=) :: TypeVariable -> TypeVariable -> Bool # | |
Show TypeVariable Source # | |
Defined in Language.JVM.Attribute.Signature showsPrec :: Int -> TypeVariable -> ShowS # show :: TypeVariable -> String # showList :: [TypeVariable] -> ShowS # | |
Generic TypeVariable Source # | |
Defined in Language.JVM.Attribute.Signature type Rep TypeVariable :: Type -> Type # from :: TypeVariable -> Rep TypeVariable x # to :: Rep TypeVariable x -> TypeVariable # | |
NFData TypeVariable Source # | |
Defined in Language.JVM.Attribute.Signature rnf :: TypeVariable -> () # | |
type Rep TypeVariable Source # | |
Defined in Language.JVM.Attribute.Signature type Rep TypeVariable = D1 (MetaData "TypeVariable" "Language.JVM.Attribute.Signature" "jvm-binary-0.7.0-6Ze5cHhi7ro6G13LoViNew" True) (C1 (MetaCons "TypeVariable" PrefixI True) (S1 (MetaSel (Just "tvAsText") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text))) |