{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric #-}
module Language.Java.Syntax.Types where
import Data.Data
import GHC.Generics (Generic)
data Type
= PrimType PrimType
| RefType RefType
deriving (Eq,Show,Read,Typeable,Generic,Data)
data RefType
= ClassRefType ClassType
| ArrayType Type
deriving (Eq,Show,Read,Typeable,Generic,Data)
data ClassType
= WithPackage Package ClassName
| WithoutPackage ClassName
deriving (Eq,Show,Read,Typeable,Generic,Data)
data ClassName = ClassName [(Ident, [TypeArgument])] | WildcardName
deriving (Eq,Show,Read,Typeable,Generic,Data)
data Package = FullQualiPackage [Ident] | WildcardPackage [Ident]
deriving (Eq,Show,Read,Typeable,Generic,Data)
data TypeArgument
= Wildcard (Maybe WildcardBound)
| ActualType RefType
| Diamond
deriving (Eq,Show,Read,Typeable,Generic,Data)
newtype TypeDeclSpecifier = TypeDeclSpecifier ClassType
deriving (Eq,Show,Read,Typeable,Generic,Data)
data WildcardBound
= ExtendsBound RefType
| SuperBound RefType
deriving (Eq,Show,Read,Typeable,Generic,Data)
data PrimType
= BooleanT
| ByteT
| ShortT
| IntT
| LongT
| CharT
| FloatT
| DoubleT
deriving (Eq,Show,Read,Typeable,Generic,Data,Enum,Bounded)
data TypeParam = TypeParam { typeParamName :: Ident, typeParamBounds :: [RefType] }
deriving (Eq,Show,Read,Typeable,Generic,Data)
newtype Ident = Ident String
deriving (Eq,Ord,Show,Read,Typeable,Generic,Data)
fromIdent :: Ident -> String
fromIdent (Ident s) = s
newtype Name = Name [Ident]
deriving (Eq,Ord,Show,Read,Typeable,Generic,Data)
newtype RelaxedType = RelaxedType Type
instance Eq RelaxedType where
RelaxedType (PrimType t1) == RelaxedType (PrimType t2) = t1 == t2
RelaxedType (RefType r1) == RelaxedType (PrimType r2) = checkRelaxed r1 (primToRefType r2)
RelaxedType (PrimType r1) == RelaxedType (RefType r2) = checkRelaxed (primToRefType r1) r2
RelaxedType (RefType r1) == RelaxedType (RefType r2) = checkRelaxed r1 r2
checkRelaxed :: RefType -> RefType -> Bool
checkRelaxed (ArrayType at1) (ArrayType at2) = RelaxedType at1 == RelaxedType at2
checkRelaxed (ArrayType _) (ClassRefType _) = False
checkRelaxed (ClassRefType _) (ArrayType _) = False
checkRelaxed (ClassRefType cr1) (ClassRefType cr2) = checkClassType cr1 cr2
where
checkClassType :: ClassType -> ClassType -> Bool
checkClassType (WithPackage pack1 class1) (WithPackage pack2 class2) = pack1 == pack2 && class1 `checkName` class2
checkClassType (WithPackage _ class1) (WithoutPackage class2) = class1 == class2
checkClassType (WithoutPackage class1) (WithPackage _ class2) = class1 == class2
checkClassType (WithoutPackage class1) (WithoutPackage class2) = class1 == class2
checkName :: ClassName -> ClassName -> Bool
checkName (ClassName name1) (ClassName name2) = name1 == name2
checkName _ _ = True
primToRefType :: PrimType -> RefType
primToRefType = toRefHelper
where
toRefHelper BooleanT = stringToRef "Boolean"
toRefHelper ByteT = stringToRef "Byte"
toRefHelper ShortT = stringToRef "Short"
toRefHelper IntT = stringToRef "Integer"
toRefHelper LongT = stringToRef "Long"
toRefHelper CharT = stringToRef "Char"
toRefHelper FloatT = stringToRef "Float"
toRefHelper DoubleT = stringToRef "Double"
stringToRef :: String -> RefType
stringToRef x = ClassRefType $ WithPackage refPackage (ClassName [(Ident x, [])])
refPackage :: Package
refPackage = FullQualiPackage (map Ident ["java", "lang"])
withPackageIdentToType :: [Ident] -> Ident -> Type
withPackageIdentToType packages ident = RefType $ ClassRefType $ WithPackage (FullQualiPackage packages) (ClassName [(ident, [])])
withoutPackageIdentToType :: Ident -> Type
withoutPackageIdentToType ident = RefType $ ClassRefType $ WithoutPackage $ ClassName [(ident, [])]