{-# LANGUAGE ViewPatterns #-}
module Data.GI.CodeGen.Overrides
( Overrides(pkgConfigMap, cabalPkgVersion, nsChooseVersion, girFixups,
onlineDocsMap)
, parseOverridesFile
, filterAPIsAndDeps
) where
#if !MIN_VERSION_base(4,8,0)
import Control.Applicative ((<$>))
import Data.Traversable (traverse)
#endif
import Control.Monad.Except
import Control.Monad.State
import Control.Monad.Writer (WriterT, execWriterT, tell)
import Data.Maybe (isJust)
import qualified Data.Map as M
import Data.Semigroup as Sem
import qualified Data.Set as S
import qualified Data.Text as T
import Data.Text (Text)
import qualified Data.Version as V
import Text.ParserCombinators.ReadP (readP_to_S)
import qualified System.Info as SI
import Data.GI.CodeGen.API
import qualified Text.XML as XML
import Data.GI.CodeGen.PkgConfig (tryPkgConfig)
import Data.GI.CodeGen.Util (tshow, utf8ReadFile)
import Data.GI.GIR.XMLUtils (xmlLocalName, xmlNSName,
GIRXMLNamespace(CGIRNS, GLibGIRNS, CoreGIRNS))
data Overrides = Overrides {
ignoredElems :: M.Map Name (S.Set Text),
ignoredAPIs :: S.Set Name,
sealedStructs :: S.Set Name,
allocInfo :: M.Map Name AllocationInfo,
pkgConfigMap :: M.Map Text Text,
cabalPkgVersion :: Maybe Text,
nsChooseVersion :: M.Map Text Text,
girFixups :: [GIRRule],
onlineDocsMap :: M.Map Text Text
} deriving (Show)
defaultOverrides :: Overrides
defaultOverrides = Overrides {
ignoredElems = M.empty,
ignoredAPIs = S.empty,
sealedStructs = S.empty,
allocInfo = M.empty,
pkgConfigMap = M.empty,
cabalPkgVersion = Nothing,
nsChooseVersion = M.empty,
girFixups = [],
onlineDocsMap = M.empty
}
instance Monoid Overrides where
mempty = defaultOverrides
#if !MIN_VERSION_base(4,11,0)
mappend = concatOverrides
#endif
instance Sem.Semigroup Overrides where
(<>) = concatOverrides
concatOverrides :: Overrides -> Overrides -> Overrides
concatOverrides a b = Overrides {
ignoredAPIs = ignoredAPIs a <> ignoredAPIs b,
sealedStructs = sealedStructs a <> sealedStructs b,
allocInfo = allocInfo a <> allocInfo b,
ignoredElems = M.unionWith S.union (ignoredElems a) (ignoredElems b),
pkgConfigMap = pkgConfigMap a <> pkgConfigMap b,
cabalPkgVersion = if isJust (cabalPkgVersion b)
then cabalPkgVersion b
else cabalPkgVersion a,
nsChooseVersion = nsChooseVersion a <> nsChooseVersion b,
girFixups = girFixups a <> girFixups b,
onlineDocsMap = onlineDocsMap a <> onlineDocsMap b
}
data ParserState = ParserState {
currentNS :: Maybe Text
, flags :: [Bool]
} deriving (Show)
emptyParserState :: ParserState
emptyParserState = ParserState {
currentNS = Nothing
, flags = []
}
getNS :: Parser (Maybe Text)
getNS = currentNS <$> get
withFlags :: Parser () -> Parser ()
withFlags p = do
fs <- flags <$> get
if and fs
then p
else return ()
type Parser a = WriterT Overrides (StateT ParserState (ExceptT Text IO)) a
parseOverridesFile :: FilePath -> IO (Either Text Overrides)
parseOverridesFile fname = do
overrides <- utf8ReadFile fname
runExceptT $ flip evalStateT emptyParserState $ execWriterT $
mapM (parseOneLine . T.strip) (T.lines overrides)
parseOneLine :: Text -> Parser ()
parseOneLine line | T.null line = return ()
parseOneLine (T.stripPrefix "#" -> Just _) = return ()
parseOneLine (T.stripPrefix "namespace " -> Just ns) =
withFlags $ modify' (\s -> s {currentNS = (Just . T.strip) ns})
parseOneLine (T.stripPrefix "ignore " -> Just ign) =
withFlags $ getNS >>= parseIgnore ign
parseOneLine (T.stripPrefix "seal " -> Just s) =
withFlags $ getNS >>= parseSeal s
parseOneLine (T.stripPrefix "alloc-info " -> Just s) =
withFlags $ getNS >>= parseAllocInfo s
parseOneLine (T.stripPrefix "pkg-config-name " -> Just s) =
withFlags $ parsePkgConfigName s
parseOneLine (T.stripPrefix "cabal-pkg-version " -> Just s) =
withFlags $ parseCabalPkgVersion s
parseOneLine (T.stripPrefix "namespace-version " -> Just s) =
withFlags $ parseNsVersion s
parseOneLine (T.stripPrefix "set-attr " -> Just s) =
withFlags $ parseSetAttr s
parseOneLine (T.stripPrefix "add-node " -> Just s) =
withFlags $ parseAdd s
parseOneLine (T.stripPrefix "delete-node " -> Just s) =
withFlags $ parseDelete s
parseOneLine (T.stripPrefix "C-docs-url " -> Just u) =
withFlags $ parseDocsUrl u
parseOneLine (T.stripPrefix "if " -> Just s) = parseIf s
parseOneLine (T.stripPrefix "endif" -> Just s) = parseEndif s
parseOneLine (T.stripPrefix "include " -> Just s) = parseInclude s
parseOneLine l = throwError $ "Could not understand \"" <> l <> "\"."
parseIgnore :: Text -> Maybe Text -> Parser ()
parseIgnore _ Nothing =
throwError "'ignore' requires a namespace to be defined first."
parseIgnore (T.words -> [T.splitOn "." -> [api,elem]]) (Just ns) =
tell $ defaultOverrides {ignoredElems = M.singleton (Name ns api)
(S.singleton elem)}
parseIgnore (T.words -> [T.splitOn "." -> [api]]) (Just ns) =
tell $ defaultOverrides {ignoredAPIs = S.singleton (Name ns api)}
parseIgnore ignore _ =
throwError ("Ignore syntax is of the form \"ignore API.elem\" with '.elem' optional.\nGot \"ignore " <> ignore <> "\" instead.")
parseSeal :: Text -> Maybe Text -> Parser ()
parseSeal _ Nothing = throwError "'seal' requires a namespace to be defined first."
parseSeal (T.words -> [s]) (Just ns) = tell $
defaultOverrides {sealedStructs = S.singleton (Name ns s)}
parseSeal seal _ =
throwError ("seal syntax is of the form \"seal name\".\nGot \"seal "
<> seal <> "\" instead.")
parseAllocInfo :: Text -> Maybe Text -> Parser ()
parseAllocInfo _ Nothing = throwError "'alloc-info' requires a namespace to be defined first."
parseAllocInfo (T.words -> (n:ops)) (Just ns) = do
parsedOps <- traverse parseKeyValuePair ops
info <- foldM applyOp unknownAllocationInfo parsedOps
tell $ defaultOverrides {allocInfo = M.singleton (Name ns n) info}
where applyOp :: AllocationInfo -> (Text, Text) -> Parser AllocationInfo
applyOp a ("calloc", f) = return (a {allocCalloc = AllocationOp f})
applyOp a ("copy", f) = return (a {allocCopy = AllocationOp f})
applyOp a ("free", f) = return (a {allocFree = AllocationOp f})
applyOp _ (op, _) = throwError ("Unknown alloc op \"" <> op <> "\".")
parseAllocInfo info _ =
throwError ("alloc-info syntax is of the form "
<> "\"alloc-info name calloc copy free\", with \"-\" meaning "
<> "a masked operation. Got \"alloc-info " <> info
<> "\" instead.")
parseKeyValuePair :: Text -> Parser (Text, Text)
parseKeyValuePair p =
case T.splitOn "=" p of
[k,v] -> return (k, v)
_ -> throwError ("Could not parse \"" <> p <> "\"as a \"key=value\" pair.")
parsePkgConfigName :: Text -> Parser ()
parsePkgConfigName (T.words -> [gi,pc]) = tell $
defaultOverrides {pkgConfigMap =
M.singleton (T.toLower gi) pc}
parsePkgConfigName t =
throwError ("pkg-config-name syntax is of the form\n" <>
"\t\"pkg-config-name gi-namespace pk-name\"\n" <>
"Got \"pkg-config-name " <> t <> "\" instead.")
parseNsVersion :: Text -> Parser ()
parseNsVersion (T.words -> [ns,version]) = tell $
defaultOverrides {nsChooseVersion =
M.singleton ns version}
parseNsVersion t =
throwError ("namespace-version syntax is of the form\n" <>
"\t\"namespace-version namespace version\"\n" <>
"Got \"namespace-version " <> t <> "\" instead.")
parseCabalPkgVersion :: Text -> Parser ()
parseCabalPkgVersion (T.words -> [version]) = tell $
defaultOverrides {cabalPkgVersion = Just version}
parseCabalPkgVersion t =
throwError ("cabal-pkg-version syntax is of the form\n" <>
"\t\"cabal-pkg-version version\"\n" <>
"Got \"cabal-pkg-version " <> t <> "\" instead.")
parseSetAttr :: Text -> Parser ()
parseSetAttr (T.words -> [path, attr, newVal]) = do
pathSpec <- parsePathSpec path
parsedAttr <- parseXMLName attr
tell $ defaultOverrides {girFixups =
[GIRSetAttr (pathSpec, parsedAttr) newVal]}
parseSetAttr t =
throwError ("set-attr syntax is of the form\n" <>
"\t\"set-attr nodePath attrName newValue\"\n" <>
"Got \"set-attr " <> t <> "\" instead.")
parseAdd :: Text -> Parser ()
parseAdd (T.words -> [path, name]) = do
pathSpec <- parsePathSpec path
parsedName <- parseXMLName name
tell $ defaultOverrides {girFixups = [GIRAddNode pathSpec parsedName]}
parseAdd t =
throwError ("add-node syntax is of the form\n" <>
"\t\"add-node nodePath newName\"\n" <>
"Got \"add-node " <> t <> "\" instead.")
parseDelete :: Text -> Parser ()
parseDelete (T.words -> [path]) = do
pathSpec <- parsePathSpec path
tell $ defaultOverrides {girFixups = [GIRDeleteNode pathSpec]}
parseDelete t =
throwError ("delete-node syntax is of the form\n" <>
"\t\"delete-node nodePath\"\n" <>
"Got \"delete-node " <> t <> "\" instead.")
parseDocsUrl :: Text -> Parser ()
parseDocsUrl (T.words -> [ns, url]) = do
tell $ defaultOverrides { onlineDocsMap = M.singleton ns url }
parseDocsUrl t =
throwError ("C-docs-url syntax of of the form\n" <>
"\t\"C-docs-url namespace url\"\n" <>
"Got \"C-docs-url " <> t <> "\" instead.")
parsePathSpec :: Text -> Parser GIRPath
parsePathSpec spec = mapM parseNodeSpec (T.splitOn "/" spec)
parseGIRNameTag :: Text -> GIRNameTag
parseGIRNameTag (T.stripPrefix "~" -> Just regex) = GIRRegex regex
parseGIRNameTag t = GIRPlainName t
parseNodeSpec :: Text -> Parser GIRNodeSpec
parseNodeSpec spec = case T.splitOn "@" spec of
[n] -> return (GIRNamed (parseGIRNameTag n))
["", t] -> return (GIRType t)
[n, t] -> return (GIRTypedName t (parseGIRNameTag n))
_ -> throwError ("Could not understand node spec \""
<> spec <> "\".")
parseXMLName :: Text -> Parser XML.Name
parseXMLName a = case T.splitOn ":" a of
[n] -> return (xmlLocalName n)
["c", n] -> return (xmlNSName CGIRNS n)
["glib", n] -> return (xmlNSName GLibGIRNS n)
["core", n] -> return (xmlNSName CoreGIRNS n)
_ -> throwError ("Could not understand xml name \""
<> a <> "\".")
data OSType = Linux
| OSX
| Windows
deriving (Show)
checkOS :: String -> Parser Bool
checkOS os = return (SI.os == os)
parseVersion :: Text -> Parser V.Version
parseVersion v = (chooseFullParse . readP_to_S V.parseVersion . T.unpack) v
where chooseFullParse :: [(V.Version, String)] -> Parser V.Version
chooseFullParse [] = throwError ("Could not parse version \""
<> v <> "\".")
chooseFullParse [(parsed, "")] = return parsed
chooseFullParse (_ : rest) = chooseFullParse rest
checkPkgConfigVersion :: Text -> Text -> Text -> Parser Bool
checkPkgConfigVersion pkg op tVersion = do
version <- parseVersion tVersion
pcVersion <- liftIO (tryPkgConfig pkg) >>= \case
Nothing ->
throwError ("Could not determine pkg-config version for \""
<> pkg <> "\".")
Just (_, tv) -> parseVersion tv
case op of
"==" -> return (pcVersion == version)
"/=" -> return (pcVersion /= version)
">=" -> return (pcVersion >= version)
">" -> return (pcVersion > version)
"<=" -> return (pcVersion <= version)
"<" -> return (pcVersion < version)
_ -> throwError ("Unrecognized comparison operator \"" <> op <> "\".")
parseIf :: Text -> Parser ()
parseIf cond = case T.words cond of
[] -> throwError ("Empty 'if' condition.")
["linux"] -> checkOS "linux" >>= setFlag
["osx"] -> checkOS "darwin" >>= setFlag
["windows"] -> checkOS "mingw32" >>= setFlag
("pkg-config-version" : rest) ->
case rest of
[pkg, op, version] ->
checkPkgConfigVersion pkg op version >>= setFlag
_ -> throwError ("Syntax for `pkg-config-version' is "
<> "\"pkg op version\", got \""
<> tshow rest <> "\".")
_ -> throwError ("Unknown condition \"" <> cond <> "\".")
where setFlag :: Bool -> Parser ()
setFlag flag = modify' (\s -> s {flags = flag : flags s})
parseEndif :: Text -> Parser ()
parseEndif rest = case T.words rest of
[] -> unsetFlag
_ -> throwError ("Unexpected argument to 'endif': \""
<> rest <> "\".")
where unsetFlag :: Parser ()
unsetFlag = do
s <- get
case flags s of
_:rest -> put (s {flags = rest})
[] -> throwError ("'endif' with no matching 'if'.")
parseInclude :: Text -> Parser ()
parseInclude fname = liftIO (parseOverridesFile $ T.unpack fname) >>= \case
Left err -> throwError ("Error when parsing included '"
<> fname <> "': " <> err)
Right ovs -> tell ovs
filterMethods :: [Method] -> S.Set Text -> [Method]
filterMethods set ignores =
filter ((`S.notMember` ignores) . name . methodName) set
filterAllocInfo :: AllocationInfo -> AllocationInfo -> AllocationInfo
filterAllocInfo old new =
AllocationInfo { allocCalloc = replace (allocCalloc old) (allocCalloc new)
, allocCopy = replace (allocCopy old) (allocCopy new)
, allocFree = replace (allocFree old) (allocFree new) }
where replace :: AllocationOp -> AllocationOp -> AllocationOp
replace o AllocationOpUnknown = o
replace _ o = o
filterOneAPI :: Overrides -> (Name, API, Maybe (S.Set Text)) -> (Name, API)
filterOneAPI ovs (n, APIStruct s, maybeIgnores) =
(n, APIStruct s { structMethods = maybe (structMethods s)
(filterMethods (structMethods s))
maybeIgnores
, structFields = if n `S.member` sealedStructs ovs
then []
else structFields s
, structAllocationInfo =
let ai = structAllocationInfo s
in case M.lookup n (allocInfo ovs) of
Just info -> filterAllocInfo ai info
Nothing -> ai
})
filterOneAPI ovs (n, APIUnion u, maybeIgnores) =
(n, APIUnion u {unionMethods = maybe (unionMethods u)
(filterMethods (unionMethods u))
maybeIgnores
, unionAllocationInfo =
let ai = unionAllocationInfo u
in case M.lookup n (allocInfo ovs) of
Just info -> filterAllocInfo ai info
Nothing -> ai
})
filterOneAPI _ (n, api, Nothing) = (n, api)
filterOneAPI _ (n, APIObject o, Just ignores) =
(n, APIObject o {objMethods = filterMethods (objMethods o) ignores,
objSignals = filter ((`S.notMember` ignores) . sigName)
(objSignals o)
})
filterOneAPI ovs (n, APIInterface i, Just ignores) =
(n, APIInterface i {ifMethods = filterMethods (ifMethods i) ignores,
ifSignals = filter ((`S.notMember` ignores) . sigName)
(ifSignals i),
ifAllocationInfo =
let ai = ifAllocationInfo i
in case M.lookup n (allocInfo ovs) of
Just info -> filterAllocInfo ai info
Nothing -> ai
})
filterOneAPI _ (n, api, _) = (n, api)
filterAPIs :: Overrides -> [(Name, API)] -> [(Name, API)]
filterAPIs ovs apis = map (filterOneAPI ovs . fetchIgnores) filtered
where filtered = filter ((`S.notMember` ignoredAPIs ovs) . fst) apis
fetchIgnores (n, api) = (n, api, M.lookup n (ignoredElems ovs))
filterAPIsAndDeps :: Overrides -> GIRInfo -> [GIRInfo]
-> (M.Map Name API, M.Map Name API)
filterAPIsAndDeps ovs doc deps =
let toMap = M.fromList . filterAPIs ovs . girAPIs
in (toMap doc, M.unions (map toMap deps))