module Language.Clafer.Intermediate.TypeSystem where
import Language.Clafer.Common
import Language.Clafer.Intermediate.Intclafer hiding (uid)
import Control.Applicative
import Control.Lens ((&), (<&>), (%~))
import Control.Monad (mplus, liftM)
import Data.List (nub)
import Data.Maybe
import Prelude hiding (exp)
rootTClafer :: IType
rootTClafer = TClafer ["root"]
claferTClafer :: IType
claferTClafer = TClafer ["clafer"]
numeric :: IType -> Bool
numeric TInteger = True
numeric TReal = True
numeric TDouble = True
numeric (TMap _ ta') = numeric ta'
numeric (TUnion un') = any numeric un'
numeric _ = False
isTInteger :: IType -> Bool
isTInteger TInteger = True
isTInteger (TMap _ ta') = isTInteger ta'
isTInteger (TUnion un') = any isTInteger un'
isTInteger _ = False
isTString :: IType -> Bool
isTString TString = True
isTString (TMap _ ta') = isTString ta'
isTString (TUnion un') = any isTString un'
isTString _ = False
isTBoolean :: IType -> Bool
isTBoolean TBoolean = True
isTBoolean (TMap _ ta') = isTBoolean ta'
isTBoolean (TUnion un') = any isTBoolean un'
isTBoolean _ = False
getTClafer :: IClafer -> IType
getTClafer iClafer' = case _uid iClafer' of
"root" -> rootTClafer
"clafer" -> claferTClafer
_ -> case _super iClafer' of
Nothing -> TClafer [ _uid iClafer']
Just super' -> (fromJust $ _iType super') & hi %~ ((:) (_uid iClafer'))
getTClaferByUID :: UIDIClaferMap -> UID -> Maybe IType
getTClaferByUID uidIClaferMap' uid' = case uid' of
"root" -> Just rootTClafer
"clafer" -> Just claferTClafer
_ -> findIClafer uidIClaferMap' uid' <&> getTClafer
getTClaferFromIExp :: UIDIClaferMap -> IExp -> Maybe IType
getTClaferFromIExp uidIClaferMap' (IClaferId _ uid' _ _) = getTClaferByUID uidIClaferMap' uid'
getTClaferFromIExp _ (IInt _) = Just TInteger
getTClaferFromIExp _ (IReal _) = Just TReal
getTClaferFromIExp _ (IDouble _) = Just TDouble
getTClaferFromIExp _ (IStr _) = Just TString
getTClaferFromIExp _ _ = Nothing
getDrefTMap :: IClafer -> Maybe IType
getDrefTMap iClafer' = case _uid iClafer' of
"root" -> Nothing
"clafer" -> Nothing
_ -> TMap <$> (Just $ getTClafer iClafer') <*> (iClafer' & _reference <&> _ref >>= _iType)
getDrefTMapByUID :: UIDIClaferMap -> UID -> Maybe IType
getDrefTMapByUID uidIClaferMap' uid' = case uid' of
"root" -> Nothing
"clafer" -> Nothing
_ -> findIClafer uidIClaferMap' uid' >>= getDrefTMap
hierarchy :: (Monad m) => UIDIClaferMap -> UID -> m [IClafer]
hierarchy uidIClaferMap' uid' = case findIClafer uidIClaferMap' uid' of
Nothing -> fail $ "TypeSystem.hierarchy: clafer " ++ uid' ++ "not found!"
Just clafer -> return $ findHierarchy getSuper uidIClaferMap' clafer
hierarchyMap :: (Monad m) => UIDIClaferMap -> (IClafer -> a) -> UID -> m [a]
hierarchyMap uidIClaferMap' f c = case findIClafer uidIClaferMap' c of
Nothing -> fail $ "TypeSystem.hierarchyMap: clafer " ++ c ++ "not found!"
Just clafer -> return $ mapHierarchy f getSuper uidIClaferMap' clafer
unionType :: IType -> [String]
unionType TString = [stringType]
unionType TReal = [realType]
unionType TDouble = [doubleType]
unionType TInteger = [integerType]
unionType TBoolean = [booleanType]
unionType (TClafer u) = u
unionType (TUnion types) = concatMap unionType types
unionType (TMap _ ta') = unionType ta'
fromUnionType :: [String] -> Maybe IType
fromUnionType u =
case nub u of
["string"] -> Just TString
["integer"] -> Just TInteger
["int"] -> Just TInteger
["double"] -> Just TDouble
["real"] -> Just TReal
[] -> Nothing
u' -> Just $ TClafer u'
(+++) :: IType -> IType -> IType
TBoolean +++ TBoolean = TBoolean
TString +++ TString = TString
TReal +++ TReal = TReal
TDouble +++ TDouble = TDouble
TInteger +++ TInteger = TInteger
t1@(TClafer u1) +++ t2@(TClafer u2) = if t1 == t2
then t1
else (TClafer $ nub $ u1 ++ u2)
(TMap so1 ta1) +++ (TMap so2 ta2) = TMap (so1 +++ so2) (ta1 +++ ta2)
(TUnion un1) +++ (TUnion un2) = collapseUnion (TUnion $ nub $ un1 ++ un2)
(TUnion un1) +++ t2 = collapseUnion (TUnion $ nub $ un1 ++ [t2])
t1 +++ (TUnion un2) = collapseUnion (TUnion $ nub $ t1:un2)
t1 +++ t2 = if t1 == t2
then t1
else TUnion [t1, t2]
collapseUnion :: IType -> IType
collapseUnion (TUnion [t]) = t
collapseUnion t = t
intersection :: Monad m => UIDIClaferMap -> IType -> IType -> m (Maybe IType)
intersection _ TBoolean TBoolean = return $ Just TBoolean
intersection _ TString TString = return $ Just TString
intersection _ TReal TReal = return $ Just TReal
intersection _ TReal TDouble = return $ Just TReal
intersection _ TDouble TReal = return $ Just TReal
intersection _ TReal TInteger = return $ Just TReal
intersection _ TInteger TReal = return $ Just TReal
intersection _ TDouble TDouble = return $ Just TDouble
intersection _ TDouble TInteger = return $ Just TDouble
intersection _ TInteger TDouble = return $ Just TDouble
intersection _ TInteger TInteger = return $ Just TInteger
intersection uidIClaferMap' (TUnion t1s) t2@(TClafer _) = do
t1s' <- mapM (intersection uidIClaferMap' t2) t1s
return $ case catMaybes t1s' of
[] -> Nothing
[t] -> Just t
t1s'' -> Just $ TUnion t1s''
intersection uidIClaferMap' t1@(TClafer _) (TUnion t2s) = do
t2s' <- mapM (intersection uidIClaferMap' t1) t2s
return $ case catMaybes t2s' of
[] -> Nothing
[t] -> Just t
t2s'' -> Just $ TUnion t2s''
intersection uidIClaferMap' t@(TClafer ut1) (TClafer ut2) = if ut1 == ut2
then return $ Just t
else do
h1 <- (mapM (hierarchyMap uidIClaferMap' _uid) ut1)
h2 <- (mapM (hierarchyMap uidIClaferMap' _uid) ut2)
return $ fromUnionType $ catMaybes [contains (head u1) u2 `mplus` contains (head u2) u1 | u1 <- h1, u2 <- h2 ]
where
contains i is = if i `elem` is then Just i else Nothing
intersection uidIClaferMap' (TMap _ ta1) (TMap _ ta2) = intersection uidIClaferMap' ta1 ta2
intersection uidIClaferMap' (TMap _ ta1) ot2 = do
coercedType <- intersection uidIClaferMap' ta1 ot2
return $ if Just ta1 == coercedType then coercedType else Nothing
intersection uidIClaferMap' ot1 (TMap _ ta2) = do
coercedType <- intersection uidIClaferMap' ot1 ta2
return $ if Just ta2 == coercedType then coercedType else Nothing
intersection _ _ _ = do
return Nothing
getIfThenElseType :: Monad m => UIDIClaferMap -> IType -> IType -> m (Maybe IType)
getIfThenElseType _ TBoolean TBoolean = return $ Just TBoolean
getIfThenElseType _ TString TString = return $ Just TString
getIfThenElseType _ TReal TReal = return $ Just TReal
getIfThenElseType _ TReal TDouble = return $ Just TReal
getIfThenElseType _ TDouble TReal = return $ Just TReal
getIfThenElseType _ TReal TInteger = return $ Just TReal
getIfThenElseType _ TInteger TReal = return $ Just TReal
getIfThenElseType _ TDouble TDouble = return $ Just TDouble
getIfThenElseType _ TDouble TInteger = return $ Just TDouble
getIfThenElseType _ TInteger TDouble = return $ Just TDouble
getIfThenElseType _ TInteger TInteger = return $ Just TInteger
getIfThenElseType uidIClaferMap' (TUnion t1s) t2@(TClafer _) = undefined
getIfThenElseType uidIClaferMap' t1@(TClafer _) (TUnion t2s) = undefined
getIfThenElseType uidIClaferMap' t@(TClafer ut1) (TClafer ut2) = if ut1 == ut2
then return $ Just t
else do
h1 <- mapM (hierarchyMap uidIClaferMap' _uid) ut1
h2 <- mapM (hierarchyMap uidIClaferMap' _uid) ut2
let ut = catMaybes [commonHierarchy u1 u2 | u1 <- h1, u2 <- h2]
return $ fromUnionType ut
where
commonHierarchy :: [UID] -> [UID] -> Maybe UID
commonHierarchy h1 h2 = commonHierarchy' (reverse h1) (reverse h2) Nothing
commonHierarchy' (x:xs) (y:ys) accumulator =
if (x == y)
then
if (null xs || null ys)
then Just x
else commonHierarchy' xs ys $ Just x
else accumulator
commonHierarchy' _ _ _ = error "ResolverType.commonHierarchy' expects two non empty lists but was given at least one empty list!"
getIfThenElseType _ _ _ = return Nothing
composition :: Monad m => UIDIClaferMap -> IType -> IType -> m (Maybe IType)
composition uidIClaferMap' (TMap so1 ta1) (TMap so2 ta2) = do
_ <- intersection uidIClaferMap' ta1 so2
return $ Just $ TMap so1 ta2
composition uidIClaferMap' ot1 (TMap so2 ta2) = do
ot1' <- intersection uidIClaferMap' ot1 so2
return $ TMap <$> ot1' <*> Just ta2
composition uidIClaferMap' (TMap so1 ta1) ot2 = do
ot2' <- intersection uidIClaferMap' ta1 ot2
return $ TMap so1 <$> ot2'
composition _ _ _ = do
return Nothing
addHierarchy :: UIDIClaferMap -> IType -> IType
addHierarchy uidIClaferMap' (TClafer [uid']) = TClafer $ mapHierarchy _uid getSuper uidIClaferMap' $ fromJust $ findIClafer uidIClaferMap' uid'
addHierarchy uidIClaferMap' (TMap so' ta') = TMap (addHierarchy uidIClaferMap' so') (addHierarchy uidIClaferMap' ta')
addHierarchy uidIClaferMap' (TUnion un') = TUnion $ map (addHierarchy uidIClaferMap') un'
addHierarchy _ x = x
closure :: Monad m => UIDIClaferMap -> [String] -> m [String]
closure uidIClaferMap' ut = concat `liftM` mapM (hierarchyMap uidIClaferMap' _uid) ut
getTMaps :: UIDIClaferMap -> IType -> [IType]
getTMaps uidIClaferMap' (TClafer hi') = catMaybes $ map (getDrefTMapByUID uidIClaferMap') hi'
getTMaps uidIClaferMap' (TMap _ ta') = getTMaps uidIClaferMap' ta'
getTMaps uidIClaferMap' (TUnion un') = concatMap (getTMaps uidIClaferMap') un'
getTMaps _ _ = []
getTClafers :: UIDIClaferMap -> IType -> [IType]
getTClafers uidIClaferMap' (TClafer hi') = catMaybes $ map (getTClaferByUID uidIClaferMap') hi'
getTClafers uidIClaferMap' (TMap _ ta') = getTClafers uidIClaferMap' ta'
getTClafers uidIClaferMap' (TUnion un') = concatMap (getTClafers uidIClaferMap') un'
getTClafers _ _ = []
coerce :: IType -> IType -> IType
coerce TReal TReal = TReal
coerce TReal TInteger = TReal
coerce TInteger TReal = TReal
coerce TReal TDouble = TReal
coerce TDouble TReal = TReal
coerce TDouble TDouble = TDouble
coerce TDouble TInteger = TDouble
coerce TInteger TDouble = TDouble
coerce TInteger TInteger = TInteger
coerce (TMap _ t1) (TMap _ t2) = coerce t1 t2
coerce (TMap _ t1) t2 = coerce t1 t2
coerce t1 (TMap _ t2) = coerce t1 t2
coerce x y = error $ "TypeSystem.coerce: Cannot coerce not numeric: " ++ show x ++ " and " ++ show y
coerceRight :: IType -> IType -> Maybe IType
coerceRight lt rt = let
coercedRType = coerce lt rt
in
if lt == coercedRType then Just lt else Nothing