module Data.GI.GIR.Function
( Function(..)
, parseFunction
) where
import Data.Text (Text)
import Data.GI.GIR.Callable (Callable(..), parseCallable)
import Data.GI.GIR.Parser
data Function = Function {
Function -> Text
fnSymbol :: Text
, Function -> Maybe Text
fnMovedTo :: Maybe Text
, Function -> Callable
fnCallable :: Callable
} deriving Int -> Function -> ShowS
[Function] -> ShowS
Function -> String
(Int -> Function -> ShowS)
-> (Function -> String) -> ([Function] -> ShowS) -> Show Function
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Function] -> ShowS
$cshowList :: [Function] -> ShowS
show :: Function -> String
$cshow :: Function -> String
showsPrec :: Int -> Function -> ShowS
$cshowsPrec :: Int -> Function -> ShowS
Show
parseFunction :: Parser (Name, Function)
parseFunction :: Parser (Name, Function)
parseFunction = do
Name
name <- Parser Name
parseName
Maybe Text
shadows <- Name -> Parser (Maybe Text)
queryAttr Name
"shadows"
let exposedName :: Name
exposedName = case Maybe Text
shadows of
Just Text
n -> Name
name {name :: Text
name = Text
n}
Maybe Text
Nothing -> Name
name
Callable
callable <- Parser Callable
parseCallable
Text
symbol <- GIRXMLNamespace -> Name -> Parser Text
getAttrWithNamespace GIRXMLNamespace
CGIRNS Name
"identifier"
Maybe Text
movedTo <- Name -> Parser (Maybe Text)
queryAttr Name
"moved-to"
(Name, Function) -> Parser (Name, Function)
forall (m :: * -> *) a. Monad m => a -> m a
return ((Name, Function) -> Parser (Name, Function))
-> (Name, Function) -> Parser (Name, Function)
forall a b. (a -> b) -> a -> b
$ (Name
exposedName,
Function :: Text -> Maybe Text -> Callable -> Function
Function {
fnSymbol :: Text
fnSymbol = Text
symbol
, fnCallable :: Callable
fnCallable = Callable
callable
, fnMovedTo :: Maybe Text
fnMovedTo = Maybe Text
movedTo
})