module Data.GI.GIR.Method
( Method(..)
, MethodType(..)
, parseMethod
) where
import Data.Text (Text)
import Data.GI.GIR.Arg (Arg, parseArg)
import Data.GI.GIR.Callable (Callable(..), parseCallable)
import Data.GI.GIR.Parser
data MethodType = Constructor
| MemberFunction
| OrdinaryMethod
deriving (MethodType -> MethodType -> Bool
(MethodType -> MethodType -> Bool)
-> (MethodType -> MethodType -> Bool) -> Eq MethodType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: MethodType -> MethodType -> Bool
== :: MethodType -> MethodType -> Bool
$c/= :: MethodType -> MethodType -> Bool
/= :: MethodType -> MethodType -> Bool
Eq, Int -> MethodType -> ShowS
[MethodType] -> ShowS
MethodType -> String
(Int -> MethodType -> ShowS)
-> (MethodType -> String)
-> ([MethodType] -> ShowS)
-> Show MethodType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> MethodType -> ShowS
showsPrec :: Int -> MethodType -> ShowS
$cshow :: MethodType -> String
show :: MethodType -> String
$cshowList :: [MethodType] -> ShowS
showList :: [MethodType] -> ShowS
Show)
data Method = Method {
Method -> Name
methodName :: Name,
Method -> Text
methodSymbol :: Text,
Method -> MethodType
methodType :: MethodType,
Method -> Maybe Text
methodMovedTo :: Maybe Text,
Method -> Callable
methodCallable :: Callable
} deriving (Method -> Method -> Bool
(Method -> Method -> Bool)
-> (Method -> Method -> Bool) -> Eq Method
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Method -> Method -> Bool
== :: Method -> Method -> Bool
$c/= :: Method -> Method -> Bool
/= :: Method -> Method -> Bool
Eq, Int -> Method -> ShowS
[Method] -> ShowS
Method -> String
(Int -> Method -> ShowS)
-> (Method -> String) -> ([Method] -> ShowS) -> Show Method
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Method -> ShowS
showsPrec :: Int -> Method -> ShowS
$cshow :: Method -> String
show :: Method -> String
$cshowList :: [Method] -> ShowS
showList :: [Method] -> ShowS
Show)
parseInstanceArg :: Parser Arg
parseInstanceArg :: Parser Arg
parseInstanceArg = do
instanceInfo <- Text -> Parser [Arg] -> Parser [[Arg]]
forall a. Text -> Parser a -> Parser [a]
parseChildrenWithLocalName Text
"parameters" Parser [Arg]
parseInstPars
case instanceInfo of
[[Arg
inst]] -> Arg -> Parser Arg
forall a. a -> ReaderT ParseContext (Except Text) a
forall (m :: * -> *) a. Monad m => a -> m a
return Arg
inst
[] -> Text -> Parser Arg
forall a. Text -> Parser a
parseError (Text -> Parser Arg) -> Text -> Parser Arg
forall a b. (a -> b) -> a -> b
$ Text
"No instance-parameter found."
[[Arg]]
_ -> Text -> Parser Arg
forall a. Text -> Parser a
parseError (Text -> Parser Arg) -> Text -> Parser Arg
forall a b. (a -> b) -> a -> b
$ Text
"Too many instance parameters."
where parseInstPars :: Parser [Arg]
parseInstPars :: Parser [Arg]
parseInstPars = Text -> Parser Arg -> Parser [Arg]
forall a. Text -> Parser a -> Parser [a]
parseChildrenWithLocalName Text
"instance-parameter" Parser Arg
parseArg
parseMethod :: MethodType -> Parser Method
parseMethod :: MethodType -> Parser Method
parseMethod MethodType
mType = do
name <- Parser Name
parseName
shadows <- queryAttr "shadows"
let exposedName = case Maybe Text
shadows of
Just Text
n -> Name
name {name = n}
Maybe Text
Nothing -> Name
name
callable <- if mType /= OrdinaryMethod
then parseCallable
else do
c <- parseCallable
instanceArg <- parseInstanceArg
return $ c {args = instanceArg : args c}
symbol <- getAttrWithNamespace CGIRNS "identifier"
movedTo <- queryAttr "moved-to"
return $ Method {
methodName = exposedName
, methodSymbol = symbol
, methodType = mType
, methodMovedTo = movedTo
, methodCallable = callable
}