{-# LANGUAGE RecordWildCards, NamedFieldPuns #-}
module Data.GI.CodeGen.API
( API(..)
, GIRInfo(..)
, loadGIRInfo
, loadRawGIRInfo
, GIRRule(..)
, GIRPath
, GIRNodeSpec(..)
, GIRNameTag(..)
, Name(..)
, Transfer(..)
, AllocationInfo(..)
, AllocationOp(..)
, unknownAllocationInfo
, Direction(..)
, Scope(..)
, DeprecationInfo
, EnumerationMember(..)
, PropertyFlag(..)
, MethodType(..)
, Constant(..)
, Arg(..)
, Callable(..)
, Function(..)
, Signal(..)
, Property(..)
, Field(..)
, Struct(..)
, Callback(..)
, Interface(..)
, Method(..)
, Object(..)
, Enumeration(..)
, Flags (..)
, Union (..)
) where
#if !MIN_VERSION_base(4,8,0)
import Control.Applicative ((<$>))
#endif
import Control.Monad ((>=>), foldM, forM, forM_)
import qualified Data.List as L
import qualified Data.Map as M
import Data.Maybe (mapMaybe, catMaybes)
import Data.Monoid ((<>))
import qualified Data.Set as S
import qualified Data.Text as T
import Data.Text (Text)
import Foreign.Ptr (Ptr)
import Foreign (peek)
import Foreign.C.Types (CUInt)
import Text.XML hiding (Name)
import qualified Text.XML as XML
import Text.Regex.TDFA ((=~))
import Data.GI.GIR.Alias (documentListAliases)
import Data.GI.GIR.Allocation (AllocationInfo(..), AllocationOp(..), unknownAllocationInfo)
import Data.GI.GIR.Arg (Arg(..), Direction(..), Scope(..))
import Data.GI.GIR.BasicTypes (Alias, Name(..), Transfer(..))
import Data.GI.GIR.Callable (Callable(..))
import Data.GI.GIR.Callback (Callback(..), parseCallback)
import Data.GI.GIR.Constant (Constant(..), parseConstant)
import Data.GI.GIR.Deprecation (DeprecationInfo)
import Data.GI.GIR.Enum (Enumeration(..), EnumerationMember(..), parseEnum)
import Data.GI.GIR.Field (Field(..))
import Data.GI.GIR.Flags (Flags(..), parseFlags)
import Data.GI.GIR.Function (Function(..), parseFunction)
import Data.GI.GIR.Interface (Interface(..), parseInterface)
import Data.GI.GIR.Method (Method(..), MethodType(..))
import Data.GI.GIR.Object (Object(..), parseObject)
import Data.GI.GIR.Parser (Parser, runParser)
import Data.GI.GIR.Property (Property(..), PropertyFlag(..))
import Data.GI.GIR.Repository (readGiRepository)
import Data.GI.GIR.Signal (Signal(..))
import Data.GI.GIR.Struct (Struct(..), parseStruct)
import Data.GI.GIR.Union (Union(..), parseUnion)
import Data.GI.GIR.XMLUtils (subelements, childElemsWithLocalName, lookupAttr,
lookupAttrWithNamespace, GIRXMLNamespace(..),
xmlLocalName)
import Data.GI.Base.BasicConversions (unpackStorableArrayWithLength)
import Data.GI.Base.BasicTypes (GType(..), CGType, gtypeName)
import Data.GI.Base.Utils (allocMem, freeMem)
import Data.GI.CodeGen.LibGIRepository (girRequire, FieldInfo(..),
girStructFieldInfo, girUnionFieldInfo,
girLoadGType)
import Data.GI.CodeGen.GType (gtypeIsBoxed)
import Data.GI.CodeGen.Type (Type)
data GIRInfo = GIRInfo {
girPCPackages :: [Text],
girNSName :: Text,
girNSVersion :: Text,
girAPIs :: [(Name, API)],
girCTypes :: M.Map Text Name
} deriving Show
data GIRNamespace = GIRNamespace {
nsName :: Text,
nsVersion :: Text,
nsAPIs :: [(Name, API)],
nsCTypes :: [(Text, Name)]
} deriving (Show)
data GIRInfoParse = GIRInfoParse {
girIPPackage :: [Maybe Text],
girIPIncludes :: [Maybe (Text, Text)],
girIPNamespaces :: [Maybe GIRNamespace]
} deriving (Show)
type GIRPath = [GIRNodeSpec]
data GIRNodeSpec = GIRNamed GIRNameTag
| GIRType Text
| GIRTypedName Text GIRNameTag
deriving (Show)
data GIRNameTag = GIRPlainName Text
| GIRRegex Text
deriving (Show)
data GIRRule = GIRSetAttr (GIRPath, XML.Name) Text
| GIRAddNode GIRPath XML.Name
| GIRDeleteNode GIRPath
deriving (Show)
data API
= APIConst Constant
| APIFunction Function
| APICallback Callback
| APIEnum Enumeration
| APIFlags Flags
| APIInterface Interface
| APIObject Object
| APIStruct Struct
| APIUnion Union
deriving Show
parseAPI :: Text -> M.Map Alias Type -> Element -> (a -> API)
-> Parser (Name, a) -> (Name, API)
parseAPI ns aliases element wrapper parser =
case runParser ns aliases element parser of
Left err -> error $ "Parse error: " ++ T.unpack err
Right (n, a) -> (n, wrapper a)
parseNSElement :: M.Map Alias Type -> GIRNamespace -> Element -> GIRNamespace
parseNSElement aliases ns@GIRNamespace{..} element
| lookupAttr "introspectable" element == Just "0" = ns
| otherwise =
case nameLocalName (elementName element) of
"alias" -> ns
"constant" -> parse APIConst parseConstant
"enumeration" -> parse APIEnum parseEnum
"bitfield" -> parse APIFlags parseFlags
"function" -> parse APIFunction parseFunction
"callback" -> parse APICallback parseCallback
"record" -> parse APIStruct parseStruct
"union" -> parse APIUnion parseUnion
"class" -> parse APIObject parseObject
"interface" -> parse APIInterface parseInterface
"boxed" -> ns
n -> error . T.unpack $ "Unknown GIR element \"" <> n <> "\" when processing namespace \"" <> nsName <> "\", aborting."
where parse :: (a -> API) -> Parser (Name, a) -> GIRNamespace
parse wrapper parser =
let (n, api) = parseAPI nsName aliases element wrapper parser
maybeCType = lookupAttrWithNamespace CGIRNS "type" element
in ns { nsAPIs = (n, api) : nsAPIs,
nsCTypes = case maybeCType of
Just ctype -> (ctype, n) : nsCTypes
Nothing -> nsCTypes
}
parseNamespace :: Element -> M.Map Alias Type -> Maybe GIRNamespace
parseNamespace element aliases = do
let attrs = elementAttributes element
name <- M.lookup "name" attrs
version <- M.lookup "version" attrs
let ns = GIRNamespace {
nsName = name,
nsVersion = version,
nsAPIs = [],
nsCTypes = []
}
return (L.foldl' (parseNSElement aliases) ns (subelements element))
parseInclude :: Element -> Maybe (Text, Text)
parseInclude element = do
name <- M.lookup "name" attrs
version <- M.lookup "version" attrs
return (name, version)
where attrs = elementAttributes element
parsePackage :: Element -> Maybe Text
parsePackage element = M.lookup "name" (elementAttributes element)
parseRootElement :: M.Map Alias Type -> GIRInfoParse -> Element -> GIRInfoParse
parseRootElement aliases info@GIRInfoParse{..} element =
case nameLocalName (elementName element) of
"include" -> info {girIPIncludes = parseInclude element : girIPIncludes}
"package" -> info {girIPPackage = parsePackage element : girIPPackage}
"namespace" -> info {girIPNamespaces = parseNamespace element aliases : girIPNamespaces}
_ -> info
emptyGIRInfoParse :: GIRInfoParse
emptyGIRInfoParse = GIRInfoParse {
girIPPackage = [],
girIPIncludes = [],
girIPNamespaces = []
}
parseGIRDocument :: M.Map Alias Type -> Document -> GIRInfoParse
parseGIRDocument aliases doc = L.foldl' (parseRootElement aliases) emptyGIRInfoParse (subelements (documentRoot doc))
documentListIncludes :: Document -> S.Set (Text, Text)
documentListIncludes doc = S.fromList (mapMaybe parseInclude includes)
where includes = childElemsWithLocalName "include" (documentRoot doc)
loadDependencies :: Bool
-> S.Set (Text, Text)
-> M.Map (Text, Text) Document
-> [FilePath]
-> [GIRRule]
-> IO (M.Map (Text, Text) Document)
loadDependencies verbose requested loaded extraPaths rules
| S.null requested = return loaded
| otherwise = do
let (name, version) = S.elemAt 0 requested
doc <- fixupGIRDocument rules <$>
readGiRepository verbose name (Just version) extraPaths
let newLoaded = M.insert (name, version) doc loaded
loadedSet = S.fromList (M.keys newLoaded)
newRequested = S.union requested (documentListIncludes doc)
notYetLoaded = S.difference newRequested loadedSet
loadDependencies verbose notYetLoaded newLoaded extraPaths rules
loadGIRFile :: Bool
-> Text
-> Maybe Text
-> [FilePath]
-> [GIRRule]
-> IO (Document,
M.Map (Text, Text) Document)
loadGIRFile verbose name version extraPaths rules = do
doc <- fixupGIRDocument rules <$>
readGiRepository verbose name version extraPaths
deps <- loadDependencies verbose (documentListIncludes doc) M.empty
extraPaths rules
return (doc, deps)
toGIRInfo :: GIRInfoParse -> Either Text GIRInfo
toGIRInfo info =
case catMaybes (girIPNamespaces info) of
[ns] -> Right GIRInfo {
girPCPackages = (reverse . catMaybes . girIPPackage) info
, girNSName = nsName ns
, girNSVersion = nsVersion ns
, girAPIs = reverse (nsAPIs ns)
, girCTypes = M.fromList (nsCTypes ns)
}
[] -> Left "Found no valid namespace."
_ -> Left "Found multiple namespaces."
loadRawGIRInfo :: Bool
-> Text
-> Maybe Text
-> [FilePath]
-> IO GIRInfo
loadRawGIRInfo verbose name version extraPaths = do
doc <- readGiRepository verbose name version extraPaths
case toGIRInfo (parseGIRDocument M.empty doc) of
Left err -> error . T.unpack $ "Error when raw parsing \"" <> name <> "\": " <> err
Right docGIR -> return docGIR
loadGIRInfo :: Bool
-> Text
-> Maybe Text
-> [FilePath]
-> [GIRRule]
-> IO (GIRInfo,
[GIRInfo])
loadGIRInfo verbose name version extraPaths rules = do
(doc, deps) <- loadGIRFile verbose name version extraPaths rules
let aliases = M.unions (map documentListAliases (doc : M.elems deps))
parsedDoc = toGIRInfo (parseGIRDocument aliases doc)
parsedDeps = map (toGIRInfo . parseGIRDocument aliases) (M.elems deps)
case combineErrors parsedDoc parsedDeps of
Left err -> error . T.unpack $ "Error when parsing \"" <> name <> "\": " <> err
Right (docGIR, depsGIR) -> do
if girNSName docGIR == name
then do
forM_ (docGIR : depsGIR) $ \info ->
girRequire (girNSName info) (girNSVersion info)
(fixedDoc, fixedDeps) <- fixupGIRInfos docGIR depsGIR
return (fixedDoc, fixedDeps)
else error . T.unpack $ "Got unexpected namespace \""
<> girNSName docGIR <> "\" when parsing \"" <> name <> "\"."
where combineErrors :: Either Text GIRInfo -> [Either Text GIRInfo]
-> Either Text (GIRInfo, [GIRInfo])
combineErrors parsedDoc parsedDeps = do
doc <- parsedDoc
deps <- sequence parsedDeps
return (doc, deps)
foreign import ccall "g_type_interface_prerequisites" g_type_interface_prerequisites :: CGType -> Ptr CUInt -> IO (Ptr CGType)
gtypeInterfaceListPrereqs :: GType -> IO [Text]
gtypeInterfaceListPrereqs (GType cgtype) = do
nprereqsPtr <- allocMem :: IO (Ptr CUInt)
ps <- g_type_interface_prerequisites cgtype nprereqsPtr
nprereqs <- peek nprereqsPtr
psCGTypes <- unpackStorableArrayWithLength nprereqs ps
freeMem ps
freeMem nprereqsPtr
mapM (fmap T.pack . gtypeName . GType) psCGTypes
fixupInterface :: M.Map Text Name -> (Name, API) -> IO (Name, API)
fixupInterface csymbolMap (n@(Name ns _), APIInterface iface) = do
prereqs <- case ifTypeInit iface of
Nothing -> return []
Just ti -> do
gtype <- girLoadGType ns ti
prereqGTypes <- gtypeInterfaceListPrereqs gtype
forM prereqGTypes $ \p -> do
case M.lookup p csymbolMap of
Just pn -> return pn
Nothing -> error $ "Could not find prerequisite type " ++ show p ++ " for interface " ++ show n
return (n, APIInterface (iface {ifPrerequisites = prereqs}))
fixupInterface _ (n, api) = return (n, api)
fixupStruct :: M.Map Text Name -> (Name, API) -> IO (Name, API)
fixupStruct _ (n, APIStruct s) = do
fixed <- (fixupStructIsBoxed n >=> fixupStructSizeAndOffsets n) s
return (n, APIStruct fixed)
fixupStruct _ api = return api
fixupStructIsBoxed :: Name -> Struct -> IO Struct
fixupStructIsBoxed (Name "GLib" "Variant") s =
return (s {structIsBoxed = False})
fixupStructIsBoxed (Name ns _) s = do
isBoxed <- case structTypeInit s of
Nothing -> return False
Just ti -> do
gtype <- girLoadGType ns ti
return (gtypeIsBoxed gtype)
return (s {structIsBoxed = isBoxed})
fixupStructSizeAndOffsets :: Name -> Struct -> IO Struct
fixupStructSizeAndOffsets (Name ns n) s = do
(size, infoMap) <- girStructFieldInfo ns n
return (s { structSize = size
, structFields = map (fixupField infoMap) (structFields s)})
fixupUnion :: M.Map Text Name -> (Name, API) -> IO (Name, API)
fixupUnion _ (n, APIUnion u) = do
fixed <- (fixupUnionSizeAndOffsets n) u
return (n, APIUnion fixed)
fixupUnion _ api = return api
fixupUnionSizeAndOffsets :: Name -> Union -> IO Union
fixupUnionSizeAndOffsets (Name ns n) u = do
(size, infoMap) <- girUnionFieldInfo ns n
return (u { unionSize = size
, unionFields = map (fixupField infoMap) (unionFields u)})
fixupField :: M.Map Text FieldInfo -> Field -> Field
fixupField offsetMap f =
f {fieldOffset = case M.lookup (fieldName f) offsetMap of
Nothing -> error $ "Could not find field "
++ show (fieldName f)
Just o -> fieldInfoOffset o }
fixupGIRInfos :: GIRInfo -> [GIRInfo] -> IO (GIRInfo, [GIRInfo])
fixupGIRInfos doc deps = (fixup fixupInterface >=>
fixup fixupStruct >=>
fixup fixupUnion) (doc, deps)
where fixup :: (M.Map Text Name -> (Name, API) -> IO (Name, API))
-> (GIRInfo, [GIRInfo]) -> IO (GIRInfo, [GIRInfo])
fixup fixer (doc, deps) = do
fixedDoc <- fixAPIs fixer doc
fixedDeps <- mapM (fixAPIs fixer) deps
return (fixedDoc, fixedDeps)
fixAPIs :: (M.Map Text Name -> (Name, API) -> IO (Name, API)) -> GIRInfo -> IO GIRInfo
fixAPIs fixer info = do
fixedAPIs <- mapM (fixer ctypes) (girAPIs info)
return $ info {girAPIs = fixedAPIs}
ctypes :: M.Map Text Name
ctypes = M.unions (map girCTypes (doc:deps))
fixupGIRDocument :: [GIRRule] -> XML.Document -> XML.Document
fixupGIRDocument rules doc =
doc {XML.documentRoot = fixupGIR rules (XML.documentRoot doc)}
fixupGIR :: [GIRRule] -> XML.Element -> XML.Element
fixupGIR rules elem =
elem {XML.elementNodes =
mapMaybe (\e -> foldM applyGIRRule e rules) (XML.elementNodes elem)}
where applyGIRRule :: XML.Node -> GIRRule -> Maybe XML.Node
applyGIRRule n (GIRSetAttr (path, attr) newVal) =
Just $ girSetAttr (path, attr) newVal n
applyGIRRule n (GIRAddNode path new) =
Just $ girAddNode path new n
applyGIRRule n (GIRDeleteNode path) =
girDeleteNodes path n
girSetAttr :: (GIRPath, XML.Name) -> Text -> XML.Node -> XML.Node
girSetAttr (spec:rest, attr) newVal n@(XML.NodeElement elem) =
if specMatch spec n
then case rest of
[] -> XML.NodeElement (elem {XML.elementAttributes =
M.insert attr newVal
(XML.elementAttributes elem)})
_ -> XML.NodeElement (elem {XML.elementNodes =
map (girSetAttr (rest, attr) newVal)
(XML.elementNodes elem)})
else n
girSetAttr _ _ n = n
girAddNode :: GIRPath -> XML.Name -> XML.Node -> XML.Node
girAddNode (spec:rest) newNode n@(XML.NodeElement element) =
if specMatch spec n
then case rest of
[] -> let newElement = XML.Element { elementName = newNode
, elementAttributes = M.empty
, elementNodes = [] }
nodeElementName (XML.NodeElement e) =
(Just . nameLocalName . elementName) e
nodeElementName _ = Nothing
nodeNames = mapMaybe nodeElementName (XML.elementNodes element)
in if nameLocalName newNode `elem` nodeNames
then n
else XML.NodeElement (element {XML.elementNodes =
XML.elementNodes element <>
[XML.NodeElement newElement]})
_ -> XML.NodeElement (element {XML.elementNodes =
map (girAddNode rest newNode)
(XML.elementNodes element)})
else n
girAddNode _ _ n = n
girDeleteNodes :: GIRPath -> XML.Node -> Maybe XML.Node
girDeleteNodes (spec:rest) n@(XML.NodeElement elem) =
if specMatch spec n
then case rest of
[] -> Nothing
_ -> Just $ XML.NodeElement (elem {XML.elementNodes =
mapMaybe (girDeleteNodes rest)
(XML.elementNodes elem)})
else Just n
girDeleteNodes _ n = Just n
lookupAndMatch :: GIRNameTag -> M.Map XML.Name Text -> XML.Name -> Bool
lookupAndMatch tag attrs attr =
case M.lookup attr attrs of
Just s -> case tag of
GIRPlainName pn -> s == pn
GIRRegex r -> T.unpack s =~ T.unpack r
Nothing -> False
specMatch :: GIRNodeSpec -> XML.Node -> Bool
specMatch (GIRType t) (XML.NodeElement elem) =
XML.nameLocalName (XML.elementName elem) == t
specMatch (GIRNamed name) (XML.NodeElement elem) =
lookupAndMatch name (XML.elementAttributes elem) (xmlLocalName "name")
specMatch (GIRTypedName t name) (XML.NodeElement elem) =
XML.nameLocalName (XML.elementName elem) == t &&
lookupAndMatch name (XML.elementAttributes elem) (xmlLocalName "name")
specMatch _ _ = False