module Data.GI.CodeGen.Fixups
( dropMovedItems
, guessPropertyNullability
, detectGObject
, dropDuplicatedFields
) where
import Data.Maybe (isNothing, isJust)
import Data.Monoid ((<>))
import qualified Data.Set as S
import qualified Data.Text as T
import Data.GI.CodeGen.API
dropMovedItems :: API -> Maybe API
dropMovedItems (APIFunction f) = if fnMovedTo f == Nothing
then Just (APIFunction f)
else Nothing
dropMovedItems (APIInterface i) =
(Just . APIInterface) i {ifMethods = filterMovedMethods (ifMethods i)}
dropMovedItems (APIObject o) =
(Just . APIObject) o {objMethods = filterMovedMethods (objMethods o)}
dropMovedItems (APIStruct s) =
(Just . APIStruct) s {structMethods = filterMovedMethods (structMethods s)}
dropMovedItems (APIUnion u) =
(Just . APIUnion) u {unionMethods = filterMovedMethods (unionMethods u)}
dropMovedItems a = Just a
filterMovedMethods :: [Method] -> [Method]
filterMovedMethods = filter (isNothing . methodMovedTo)
guessPropertyNullability :: (Name, API) -> (Name, API)
guessPropertyNullability (n, APIObject obj) =
(n, APIObject (guessObjectPropertyNullability obj))
guessPropertyNullability (n, APIInterface iface) =
(n, APIInterface (guessInterfacePropertyNullability iface))
guessPropertyNullability other = other
guessObjectPropertyNullability :: Object -> Object
guessObjectPropertyNullability obj =
obj {objProperties = map (guessNullability (objMethods obj))
(objProperties obj)}
guessInterfacePropertyNullability :: Interface -> Interface
guessInterfacePropertyNullability iface =
iface {ifProperties = map (guessNullability (ifMethods iface))
(ifProperties iface)}
guessNullability :: [Method] -> Property -> Property
guessNullability methods = guessReadNullability methods
. guessWriteNullability methods
guessReadNullability :: [Method] -> Property -> Property
guessReadNullability methods p
| isJust (propReadNullable p) = p
| otherwise = p {propReadNullable = nullableGetter}
where
nullableGetter :: Maybe Bool
nullableGetter =
let prop_name = T.replace "-" "_" (propName p)
in case findMethod methods ("get_" <> prop_name) of
Nothing -> Nothing
Just m ->
let c = methodCallable m
in if length (args c) == 1 &&
returnType c == Just (propType p) &&
returnTransfer c == TransferNothing &&
skipReturn c == False &&
callableThrows c == False &&
methodType m == OrdinaryMethod &&
methodMovedTo m == Nothing
then Just (returnMayBeNull c)
else Nothing
guessWriteNullability :: [Method] -> Property -> Property
guessWriteNullability methods p
| isJust (propWriteNullable p) = p
| otherwise = p {propWriteNullable = nullableSetter}
where
nullableSetter :: Maybe Bool
nullableSetter =
let prop_name = T.replace "-" "_" (propName p)
in case findMethod methods ("set_" <> prop_name) of
Nothing -> Nothing
Just m ->
let c = methodCallable m
in if length (args c) == 2 &&
(argType . last . args) c == propType p &&
returnType c == Nothing &&
(transfer . last . args) c == TransferNothing &&
(direction . last . args) c == DirectionIn &&
methodMovedTo m == Nothing &&
methodType m == OrdinaryMethod &&
callableThrows c == False
then Just ((mayBeNull . last . args) c)
else Nothing
findMethod :: [Method] -> T.Text -> Maybe Method
findMethod methods n = case filter ((== n) . name . methodName) methods of
[m] -> Just m
_ -> Nothing
detectGObject :: (Name, API) -> (Name, API)
detectGObject (n, APIInterface iface) =
if not (null (ifProperties iface) && null (ifSignals iface))
then let gobject = Name "GObject" "Object"
in if gobject `elem` (ifPrerequisites iface)
then (n, APIInterface iface)
else (n, APIInterface (iface {ifPrerequisites =
gobject : ifPrerequisites iface}))
else (n, APIInterface iface)
detectGObject api = api
dropDuplicatedEnumFields :: Enumeration -> Enumeration
dropDuplicatedEnumFields enum =
enum{enumMembers = dropDuplicates S.empty (enumMembers enum)}
where dropDuplicates :: S.Set T.Text -> [EnumerationMember] -> [EnumerationMember]
dropDuplicates _ [] = []
dropDuplicates previous (m:ms) =
if enumMemberName m `S.member` previous
then dropDuplicates previous ms
else m : dropDuplicates (S.insert (enumMemberName m) previous) ms
dropDuplicatedFields :: (Name, API) -> (Name, API)
dropDuplicatedFields (n, APIFlags (Flags enum)) =
(n, APIFlags (Flags $ dropDuplicatedEnumFields enum))
dropDuplicatedFields (n, api) = (n, api)