{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE ViewPatterns #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE OverloadedStrings #-}
module Language.JVM.Type
(
ClassName(classNameAsText)
, textCls
, textClsOrFail
, strClsOrFail
, dotCls
, unsafeTextCls
, parseClassName
, serializeClassName
, JType(..)
, jTypeSize
, parseJType
, serializeJType
, JBaseType(..)
, jBaseTypeToChar
, jBaseTypeSize
, parseJBaseType
, serializeJBaseType
, JRefType(..)
, refTypeDepth
, parseJRefType
, serializeJRefType
, parseFlatJRefType
, serializeFlatJRefType
, MethodDescriptor(..)
, parseMethodDescriptor
, serializeMethodDescriptor
, ReturnDescriptor(..)
, parseReturnDescriptor
, serializeReturnDescriptor
, FieldDescriptor(..)
, parseFieldDescriptor
, serializeFieldDescriptor
, NameAndType(..)
, parseNameAndType
, serializeNameAndType
, WithName(..)
, AsNameAndType(..)
, MethodId(..)
, parseMethodId
, serializeMethodId
, FieldId(..)
, parseFieldId
, serializeFieldId
, InClass(..)
, parseInClass
, serializeInClass
, InRefType(..)
, parseInRefType
, serializeInRefType
, inRefTypeAsInClass
, AbsMethodId(..)
, parseAbsMethodId
, serializeAbsMethodId
, AbsFieldId(..)
, parseAbsFieldId
, serializeAbsFieldId
, module Language.JVM.TextSerializable
)
where
import Data.String
import Control.Applicative
import Data.Semigroup
import GHC.Generics ( Generic )
import Prelude hiding ( takeWhile )
import Control.DeepSeq ( NFData )
import Data.Attoparsec.Text
import qualified Data.Text as Text
import Data.Text.Lazy.Builder as Builder
import Language.JVM.TextSerializable
newtype ClassName = ClassName
{ classNameAsText :: Text.Text
} deriving (Eq, Ord, Generic, NFData)
textCls :: Text.Text -> Either String ClassName
textCls = deserialize
unsafeTextCls :: Text.Text -> ClassName
unsafeTextCls = ClassName
strClsOrFail :: String -> ClassName
strClsOrFail = textClsOrFail . Text.pack
textClsOrFail :: Text.Text -> ClassName
textClsOrFail = either error id . deserialize
dotCls :: Text.Text -> Either String ClassName
dotCls = textCls . Text.map (\c -> if c == '.' then '/' else c)
parseClassName :: Parser ClassName
parseClassName = ClassName <$> takeWhile1 (notInClass ".;[<>:") <?> "ClassName"
serializeClassName :: ClassName -> Builder
serializeClassName = Builder.fromText . classNameAsText
instance TextSerializable ClassName where
parseText = parseClassName
toBuilder = serializeClassName
data JRefType
= JTClass !ClassName
| JTArray !JType
deriving (Eq, Ord, Generic, NFData)
refTypeDepth :: JRefType -> Int
refTypeDepth = \case
JTArray (JTRef a) -> 1 + refTypeDepth a
JTArray _ -> 1
JTClass _ -> 0
parseJRefType :: Parser JRefType
parseJRefType =
choice
[ JTArray <$> (char '[' *> parseJType)
, JTClass <$> (char 'L' *> parseClassName <* char ';')
]
<?> "JRefType"
serializeJRefType :: JRefType -> Builder
serializeJRefType = \case
JTArray a -> "[" <> serializeJType a
JTClass a -> "L" <> serializeClassName a <> ";"
instance TextSerializable JRefType where
parseText = parseJRefType
toBuilder = serializeJRefType
parseFlatJRefType :: Parser JRefType
parseFlatJRefType =
choice [JTArray <$> (char '[' *> parseJType), JTClass <$> parseClassName]
<?> "flat JRefType"
serializeFlatJRefType :: JRefType -> Builder
serializeFlatJRefType = \case
JTArray a -> "[" <> serializeJType a
JTClass a -> serializeClassName a
data JBaseType
= JTByte
| JTChar
| JTDouble
| JTFloat
| JTInt
| JTLong
| JTShort
| JTBoolean
deriving (Eq, Ord, Generic, NFData)
jBaseTypeToChar :: JBaseType -> Char
jBaseTypeToChar = \case
JTByte -> 'B'
JTChar -> 'C'
JTDouble -> 'D'
JTFloat -> 'F'
JTInt -> 'I'
JTLong -> 'J'
JTShort -> 'S'
JTBoolean -> 'Z'
jBaseTypeSize :: JBaseType -> Int
jBaseTypeSize = \case
JTDouble -> 2
JTLong -> 2
_ -> 1
parseJBaseType :: Parser JBaseType
parseJBaseType = try . (<?> "JBaseType") $ anyChar >>= \case
'B' -> return JTByte
'C' -> return JTChar
'D' -> return JTDouble
'F' -> return JTFloat
'I' -> return JTInt
'J' -> return JTLong
'S' -> return JTShort
'Z' -> return JTBoolean
s -> fail $ "Unknown char " ++ show s
serializeJBaseType :: JBaseType -> Builder
serializeJBaseType = Builder.singleton . jBaseTypeToChar
instance TextSerializable JBaseType where
parseText = parseJBaseType
toBuilder = serializeJBaseType
data JType
= JTBase !JBaseType
| JTRef !JRefType
deriving (Eq, Ord, Generic, NFData)
parseJType :: Parser JType
parseJType =
choice [JTRef <$> parseJRefType, JTBase <$> parseJBaseType] <?> "JType"
serializeJType :: JType -> Builder
serializeJType = \case
JTRef r -> serializeJRefType r
JTBase r -> serializeJBaseType r
instance TextSerializable JType where
parseText = parseJType
toBuilder = serializeJType
jTypeSize :: JType -> Int
jTypeSize = \case
JTBase a -> jBaseTypeSize a
JTRef _ -> 1
newtype ReturnDescriptor =
ReturnDescriptor { asMaybeJType :: Maybe JType }
deriving (Ord, Eq, Generic, NFData)
parseReturnDescriptor :: Parser ReturnDescriptor
parseReturnDescriptor =
ReturnDescriptor
<$> choice [char 'V' >> return Nothing, Just <$> parseJType]
<?> "return type"
serializeReturnDescriptor :: ReturnDescriptor -> Builder
serializeReturnDescriptor =
maybe (Builder.singleton 'V') serializeJType . asMaybeJType
instance TextSerializable ReturnDescriptor where
toBuilder = serializeReturnDescriptor
parseText = parseReturnDescriptor
data MethodDescriptor = MethodDescriptor
{ methodDescriptorArguments :: ! [JType]
, methodDescriptorReturnType :: ! ReturnDescriptor
} deriving (Ord, Eq, Generic, NFData)
parseMethodDescriptor :: Parser MethodDescriptor
parseMethodDescriptor = (<?> "MethodDescriptor") $ do
args <- char '(' *> (many' parseJType <?> "method arguments") <* char ')'
MethodDescriptor args <$> parseReturnDescriptor
serializeMethodDescriptor :: MethodDescriptor -> Builder
serializeMethodDescriptor (MethodDescriptor args rt) =
singleton '('
<> foldMap serializeJType args
<> singleton ')'
<> serializeReturnDescriptor rt
instance TextSerializable MethodDescriptor where
toBuilder = serializeMethodDescriptor
parseText = parseMethodDescriptor
newtype FieldDescriptor = FieldDescriptor
{ fieldDescriptorType :: JType
} deriving (Ord, Eq, Generic, NFData)
parseFieldDescriptor :: Parser FieldDescriptor
parseFieldDescriptor = (<?> "FieldDescriptor") $ do
FieldDescriptor <$> parseJType
serializeFieldDescriptor :: FieldDescriptor -> Builder
serializeFieldDescriptor = serializeJType . fieldDescriptorType
instance TextSerializable FieldDescriptor where
parseText = parseFieldDescriptor
toBuilder = serializeFieldDescriptor
data NameAndType a = NameAndType !Text.Text !a
deriving (Show, Eq, Ord, Generic, NFData)
class WithName n where
type WithNameId n
(<:>) :: Text.Text -> n -> WithNameId n
class AsNameAndType n where
type TypeDescriptor n
toNameAndType :: n -> NameAndType (TypeDescriptor n)
ntDescriptor :: n -> TypeDescriptor n
ntDescriptor (toNameAndType -> NameAndType _ d) = d
ntName :: n -> Text.Text
ntName (toNameAndType -> NameAndType t _) = t
instance AsNameAndType (NameAndType a) where
type TypeDescriptor (NameAndType a) = a
toNameAndType = id
parseNameAndType :: Parser a -> Parser (NameAndType a)
parseNameAndType parser = (<?> "NameAndType") $ do
_name <- many1 (notChar ':') <* char ':'
NameAndType (Text.pack _name) <$> parser
serializeNameAndType :: (a -> Builder) -> NameAndType a -> Builder
serializeNameAndType serializer (NameAndType _name descr) =
fromText _name <> ":" <> serializer descr
newtype FieldId =
FieldId { fieldIdAsNameAndType :: NameAndType FieldDescriptor }
deriving (Ord, Eq, Generic, NFData)
parseFieldId :: Parser FieldId
parseFieldId = FieldId <$> parseNameAndType parseFieldDescriptor
serializeFieldId :: FieldId -> Builder
serializeFieldId =
serializeNameAndType serializeFieldDescriptor . fieldIdAsNameAndType
instance TextSerializable FieldId where
parseText = parseFieldId
toBuilder = serializeFieldId
instance WithName FieldDescriptor where
type WithNameId FieldDescriptor = FieldId
t <:> mt = FieldId (NameAndType t mt)
instance AsNameAndType FieldId where
type TypeDescriptor FieldId = FieldDescriptor
toNameAndType = fieldIdAsNameAndType
newtype MethodId =
MethodId { methodIdAsNameAndType :: NameAndType MethodDescriptor }
deriving (Ord, Eq, Generic, NFData)
parseMethodId :: Parser MethodId
parseMethodId = MethodId <$> parseNameAndType parseMethodDescriptor
serializeMethodId :: MethodId -> Builder
serializeMethodId =
serializeNameAndType serializeMethodDescriptor . methodIdAsNameAndType
instance TextSerializable MethodId where
parseText = parseMethodId
toBuilder = serializeMethodId
instance WithName MethodDescriptor where
type WithNameId MethodDescriptor = MethodId
t <:> mt = MethodId (NameAndType t mt)
instance AsNameAndType MethodId where
type TypeDescriptor MethodId = MethodDescriptor
toNameAndType = methodIdAsNameAndType
data InClass a = InClass
{ inClassName :: !ClassName
, inClassId :: !a
} deriving (Eq, Ord, Generic, NFData)
parseInClass :: Parser a -> Parser (InClass a)
parseInClass parseClassId =
InClass <$> parseClassName <*> (char '.' *> parseClassId)
serializeInClass :: (a -> Builder) -> InClass a -> Builder
serializeInClass serializeClassId (InClass n cid) =
serializeClassName n <> singleton '.' <> serializeClassId cid
data InRefType a = InRefType
{ inRefType :: !JRefType
, inRefTypeId :: !a
} deriving (Eq, Ord, Generic, NFData)
parseInRefType :: Parser a -> Parser (InRefType a)
parseInRefType parseRefTypeId =
InRefType <$> parseJRefType <*> (char '.' *> parseRefTypeId)
serializeInRefType :: (a -> Builder) -> InRefType a -> Builder
serializeInRefType serializeRefTypeId (InRefType n cid) =
serializeJRefType n <> singleton '.' <> serializeRefTypeId cid
inRefTypeAsInClass :: InRefType a -> InClass a
inRefTypeAsInClass (InRefType rt rtid) = InClass
(case rt of
JTArray _ -> "java/lang/Object"
JTClass a -> a
)
rtid
newtype AbsFieldId =
AbsFieldId { absFieldAsInClass :: InClass FieldId }
deriving (Ord, Eq, Generic, NFData)
parseAbsFieldId :: Parser AbsFieldId
parseAbsFieldId = AbsFieldId <$> parseInClass parseFieldId
serializeAbsFieldId :: AbsFieldId -> Builder
serializeAbsFieldId = serializeInClass serializeFieldId . absFieldAsInClass
instance TextSerializable AbsFieldId where
parseText = parseAbsFieldId
toBuilder = serializeAbsFieldId
newtype AbsMethodId =
AbsMethodId { absMethodAsInClass :: InClass MethodId }
deriving (Ord, Eq, Generic, NFData)
parseAbsMethodId :: Parser AbsMethodId
parseAbsMethodId = AbsMethodId <$> parseInClass parseMethodId
serializeAbsMethodId :: AbsMethodId -> Builder
serializeAbsMethodId = serializeInClass serializeMethodId . absMethodAsInClass
instance TextSerializable AbsMethodId where
parseText = parseAbsMethodId
toBuilder = serializeAbsMethodId
deriveFromTextSerializable ''ClassName
deriveFromTextSerializable ''JType
deriveFromTextSerializable ''JRefType
deriveFromTextSerializable ''JBaseType
deriveFromTextSerializable ''FieldDescriptor
deriveFromTextSerializable ''MethodDescriptor
deriveFromTextSerializable ''ReturnDescriptor
deriveFromTextSerializable ''MethodId
deriveFromTextSerializable ''FieldId
deriveFromTextSerializable ''AbsMethodId
deriveFromTextSerializable ''AbsFieldId
deriving instance Show a => Show (InClass a)
deriving instance Show a => Show (InRefType a)