{-# LANGUAGE ScopedTypeVariables #-}
module Data.GI.CodeGen.Inheritance
( fullObjectPropertyList
, fullInterfacePropertyList
, fullObjectSignalList
, fullInterfaceSignalList
, fullObjectMethodList
, fullInterfaceMethodList
, instanceTree
) where
#if !MIN_VERSION_base(4,8,0)
import Control.Applicative ((<$>), (<*>))
#endif
import Control.Monad (foldM, when)
import qualified Data.Map as M
import Data.Monoid ((<>))
import Data.Text (Text)
import Data.GI.CodeGen.API
import Data.GI.CodeGen.Code (findAPIByName, CodeGen, line)
import Data.GI.CodeGen.Util (tshow)
getParent :: API -> Maybe Name
getParent (APIObject o) = rename $ objParent o
where
rename :: Maybe Name -> Maybe Name
rename (Just (Name "GObject" "InitiallyUnowned")) =
Just (Name "GObject" "Object")
rename x = x
getParent _ = Nothing
instanceTree :: Name -> CodeGen [Name]
instanceTree n = do
api <- findAPIByName n
case getParent api of
Just p -> (p :) <$> instanceTree p
Nothing -> return []
class Inheritable i where
ifInheritables :: Interface -> [i]
objInheritables :: Object -> [i]
iName :: i -> Text
instance Inheritable Property where
ifInheritables = ifProperties
objInheritables = objProperties
iName = propName
instance Inheritable Signal where
ifInheritables = ifSignals
objInheritables = objSignals
iName = sigName
instance Inheritable Method where
ifInheritables = ifMethods
objInheritables = objMethods
iName = name . methodName
apiInheritables :: Inheritable i => Name -> CodeGen [(Name, i)]
apiInheritables n = do
api <- findAPIByName n
case api of
APIInterface iface -> return $ map ((,) n) (ifInheritables iface)
APIObject object -> return $ map ((,) n) (objInheritables object)
_ -> error $ "apiInheritables : Unexpected API : " ++ show n
fullAPIInheritableList :: Inheritable i => Name -> CodeGen [(Name, i)]
fullAPIInheritableList n = do
api <- findAPIByName n
case api of
APIInterface iface -> fullInterfaceInheritableList n iface
APIObject object -> fullObjectInheritableList n object
_ -> error $ "FullAPIInheritableList : Unexpected API : " ++ show n
fullObjectInheritableList :: Inheritable i => Name -> Object ->
CodeGen [(Name, i)]
fullObjectInheritableList n obj = do
iT <- instanceTree n
(++) <$> (concat <$> mapM apiInheritables (n : iT))
<*> (concat <$> mapM apiInheritables (objInterfaces obj))
fullInterfaceInheritableList :: Inheritable i => Name -> Interface ->
CodeGen [(Name, i)]
fullInterfaceInheritableList n iface =
(++) (map ((,) n) (ifInheritables iface))
<$> (concat <$> mapM fullAPIInheritableList (ifPrerequisites iface))
removeDuplicates :: forall i. (Eq i, Show i, Inheritable i) =>
Bool -> [(Name, i)] -> CodeGen [(Name, i)]
removeDuplicates verbose inheritables =
(filterTainted . M.toList) <$> foldM filterDups M.empty inheritables
where
filterDups :: M.Map Text (Bool, Name, i) -> (Name, i) ->
CodeGen (M.Map Text (Bool, Name, i))
filterDups m (name, prop) =
case M.lookup (iName prop) m of
Just (tainted, n, p)
| tainted -> return m
| (p == prop) -> return m
| otherwise ->
do when verbose $ do
line "--- XXX Duplicated object with different types:"
line $ " --- " <> tshow n <> " -> " <> tshow p
line $ " --- " <> tshow name <> " -> " <> tshow prop
return $ M.insert (iName prop) (True, n, p) m
Nothing -> return $ M.insert (iName prop) (False, name, prop) m
filterTainted :: [(Text, (Bool, Name, i))] -> [(Name, i)]
filterTainted xs =
[(name, prop) | (_, (_, name, prop)) <- xs]
fullObjectPropertyList :: Name -> Object -> CodeGen [(Name, Property)]
fullObjectPropertyList n o = fullObjectInheritableList n o >>=
removeDuplicates True
fullInterfacePropertyList :: Name -> Interface -> CodeGen [(Name, Property)]
fullInterfacePropertyList n i = fullInterfaceInheritableList n i >>=
removeDuplicates True
fullObjectSignalList :: Name -> Object -> CodeGen [(Name, Signal)]
fullObjectSignalList n o = fullObjectInheritableList n o >>=
removeDuplicates True
fullInterfaceSignalList :: Name -> Interface -> CodeGen [(Name, Signal)]
fullInterfaceSignalList n i = fullInterfaceInheritableList n i >>=
removeDuplicates True
fullObjectMethodList :: Name -> Object -> CodeGen [(Name, Method)]
fullObjectMethodList n o = fullObjectInheritableList n o >>=
removeDuplicates False
fullInterfaceMethodList :: Name -> Interface -> CodeGen [(Name, Method)]
fullInterfaceMethodList n i = fullInterfaceInheritableList n i >>=
removeDuplicates False