{-# LANGUAGE Haskell2010 , DeriveDataTypeable #-} {-# OPTIONS -Wall #-} -- | -- Module : Foreign.Java.Bindings.JavaTypes -- Copyright : (c) Julian Fleischer 2013 -- License : MIT (See LICENSE file in cabal package) -- -- Maintainer : julian.fleischer@fu-berlin.de -- Stability : provisional -- Portability : non-portable (DeriveDataTypeable) -- -- Data structures that describe the interface of -- Java structures such as classes, generic types, -- their methods, etc. -- -- All types are instances of 'Data' and 'Typeable' and -- can therefor be used with /Scrap Your Boilerplate/ -- combinators (see "Data.Generics"). module Language.Java.Reflect.Types where import Data.Int import Data.Data import Data.List (nub) -- type JavaClassCache = Map (String, [JavaType]) JavaClass -- | A JavaType is either a Primitive Type, an Array, or an Object. data JavaType = JBoolean | JChar | JByte | JShort | JInt | JLong | JFloat | JDouble | JObj { typeName :: String } | JArr { componentType :: JavaType } deriving (Eq, Ord, Show, Read, Data, Typeable) printJavaType :: JavaType -> String printJavaType t = case t of JBoolean -> "boolean" JChar -> "char" JByte -> "byte" JShort -> "short" JInt -> "int" JLong -> "long" JFloat -> "float" JDouble -> "double" JObj n -> n JArr c -> printJavaType c ++ "[]" -- | The interface of a Java class. data JavaClass = JavaClass { className :: String, classParents :: [String], classIfaces :: [String], classConstructors :: [JavaConstructor], classMethods :: [JavaMethod], classFields :: [JavaField], classTypeParams :: [JavaTypeParam], classEnum :: Bool, classEnumConstants :: [(Int32, String)], classIface :: Bool, classAnnotation :: Bool, classAbstract :: Bool, classFinal :: Bool } deriving (Eq, Show, Read, Data, Typeable) data JavaClassType = Annotation | Interface | Enum | Class | Exception | Error deriving (Eq, Ord, Show, Read, Data, Typeable) classType :: JavaClass -> JavaClassType -- ^ Determines the 'JavaClassType' of a 'JavaClass'. classType clazz | "java.lang.Error" `elem` classParents clazz = Error | "java.lang.Exception" `elem` classParents clazz = Exception | classAnnotation clazz = Annotation | classIface clazz = Interface | classEnum clazz = Enum | otherwise = Class classDependencies :: JavaClass -> [String] -- ^ Calculate all classes that are referenced in any way by this class. classDependencies clazz = concat [ classParents clazz, classIfaces clazz, concatMap (fieldDependencies typeParams) (classFields clazz), concatMap (methodDependencies typeParams) (classMethods clazz), concatMap (constructorDependencies typeParams) (classConstructors clazz) ] where typeParams = classTypeParams clazz -- | A Type variable declaration. data JavaTypeParam = JavaTypeParam { paramName :: TyVar, paramBounds :: [JavaGenericType] } deriving (Eq, Ord, Show, Read, Data, Typeable) -- | A Type variable. This is merely a name. newtype TyVar = TyVar { tyVarName :: String } deriving (Eq, Ord, Show, Read, Data, Typeable) data JavaGenericType = -- | @@, @@ Wildcard { jgtBounds :: [JavaGenericType], jgtLowerBounds :: [JavaGenericType] } | -- | @java.util.List@ Parameterized { -- | The full name of the base type, e.g. @java.lang.Class@. jgtBasetype :: String, -- | The parameters. jgtParameters :: [JavaGenericType] } | -- | @X[]@ GenericArray { -- | The base type of the generic array, e.g. @java.lang.Number@. jgtComponentType :: JavaGenericType } | -- | @@ TypeVarReference { -- | The name of the type variable, e.g. @E@ or @X@. jgtName :: TyVar } | NotSoGeneric deriving (Eq, Ord, Show, Read, Data, Typeable) -- | The type of a generic type. data JavaGenericTypeType = WildcardT | ParameterizedT | GenericArrayT | TypeVarReferenceT | NotSoGenericT jgtType :: JavaGenericType -> JavaGenericTypeType -- ^ Get the type of a generic type. jgtType t = case t of (Wildcard _ _) -> WildcardT (Parameterized _ _) -> ParameterizedT (GenericArray _) -> GenericArrayT (TypeVarReference _) -> TypeVarReferenceT NotSoGeneric -> NotSoGenericT -- | The interface to a field in the Java language. data JavaField = JavaField { fieldName :: String, fieldType :: (JavaType, JavaGenericType), fieldFinal :: Bool, fieldStatic :: Bool } deriving (Eq, Show, Read, Data, Typeable) fieldDependencies :: [JavaTypeParam] -> JavaField -> [String] fieldDependencies tvars field = dependencies tvars [fieldType field] -- | The interface to a method in the Java language. data JavaMethod = JavaMethod { methodName :: String, methodName' :: String, methodParams :: [(JavaType, JavaGenericType)], methodReturnType :: (Maybe JavaType, JavaGenericType), methodExceptions :: [String], methodTypeParams :: [JavaTypeParam], methodStatic :: Bool, methodAbstract :: Bool, methodFinal :: Bool, methodNative :: Bool, methodSynchronized :: Bool } deriving (Eq, Show, Read, Data, Typeable) methodDependencies :: [JavaTypeParam] -> JavaMethod -> [String] -- ^ Return the full names of all classes that this method -- references in its definition. methodDependencies tvars method = returnDependency ++ dependencies tvars' (methodParams method) where returnDependency = case methodReturnType method of (Nothing, _) -> [] (Just t, gt) -> dependencies tvars' [(t, gt)] tvars' = methodTypeParams method ++ tvars -- it is important that the type params are appended -- up front, since lookup will return the first -- (the first is the more appropriate one, since it is -- the one in scope). -- | A Constructor in the Java language. data JavaConstructor = JavaConstructor { constructorParams :: [(JavaType, JavaGenericType)], constructorExceptions :: [String], constructorTypeParams :: [JavaTypeParam] } deriving (Eq, Show, Read, Data, Typeable) constructorDependencies :: [JavaTypeParam] -> JavaConstructor -> [String] -- ^ Retrieve all classes that this constructor definition -- references in its parameters or generic declaration. constructorDependencies tvars constr = dependencies tvars' (constructorParams constr) where tvars' = constructorTypeParams constr ++ tvars -- it is important that the type params are appended -- up front, since lookup will return the first -- (the first is the more appropriate one, since it is -- the one in scope). dependencies :: [JavaTypeParam] -> [(JavaType, JavaGenericType)] -> [String] -- ^ Discovers all types which are mentioned in a list of type declarations, -- using the type variables that are in scope. dependencies tyvars = nub . foldr (\(t, gt) ds -> deps t ++ gdeps tyvars gt ++ ds) [] where -- | Find the dependencies of an ordinary type (if any) deps t = case t of JObj c -> [c] JArr c -> deps c -- in case of an array, the dependency -- is on the component type _ -> [] -- in all other cases, it is only a primitive type -- | Find the dependencies of the generic declaration of that type -- (bounds, parameters, etc.) gdeps :: [JavaTypeParam] -> JavaGenericType -> [String] gdeps tv t = case jgtType t of WildcardT -> concatMap (gdeps tv) (jgtBounds t ++ jgtLowerBounds t) ParameterizedT -> jgtBasetype t : concatMap (gdeps tv) (jgtParameters t) GenericArrayT -> (gdeps tv) (jgtComponentType t) TypeVarReferenceT -> maybe [] (concatMap (gdeps tv') . paramBounds) (lookup tvName (zip (map paramName tv) tyvars)) NotSoGenericT -> [] where tvName = jgtName t tv' = filter ((/= tvName) . paramName) tv -- remove the current type variable so -- that we do not end up lookin it up in -- an infinite loop (*very* important)