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    -- ^ Constructs an instance of the parent type
                | MemberFunction -- ^ A function in the namespace
                | OrdinaryMethod -- ^ A function taking the parent
                                 -- instance as first argument.
                  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,
      -- | The symbol in the dynlib that this method refers to.
      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
  [[Arg]]
instanceInfo <- Text -> Parser [Arg] -> Parser [[Arg]]
forall a. Text -> Parser a -> Parser [a]
parseChildrenWithLocalName Text
"parameters" Parser [Arg]
parseInstPars
  case [[Arg]]
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
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 <- if MethodType
mType MethodType -> MethodType -> Bool
forall a. Eq a => a -> a -> Bool
/= MethodType
OrdinaryMethod
              then Parser Callable
parseCallable
              else do
                Callable
c <- Parser Callable
parseCallable
                Arg
instanceArg <- Parser Arg
parseInstanceArg
                Callable -> Parser Callable
forall a. a -> ReaderT ParseContext (Except Text) a
forall (m :: * -> *) a. Monad m => a -> m a
return (Callable -> Parser Callable) -> Callable -> Parser Callable
forall a b. (a -> b) -> a -> b
$ Callable
c {args :: [Arg]
args = Arg
instanceArg Arg -> [Arg] -> [Arg]
forall a. a -> [a] -> [a]
: Callable -> [Arg]
args Callable
c}
  Text
symbol <- GIRXMLNamespace -> Name -> Parser Text
getAttrWithNamespace GIRXMLNamespace
CGIRNS Name
"identifier"
  Maybe Text
movedTo <- Name -> Parser (Maybe Text)
queryAttr Name
"moved-to"
  Method -> Parser Method
forall a. a -> ReaderT ParseContext (Except Text) a
forall (m :: * -> *) a. Monad m => a -> m a
return (Method -> Parser Method) -> Method -> Parser Method
forall a b. (a -> b) -> a -> b
$ Method {
              methodName :: Name
methodName = Name
exposedName
            , methodSymbol :: Text
methodSymbol = Text
symbol
            , methodType :: MethodType
methodType = MethodType
mType
            , methodMovedTo :: Maybe Text
methodMovedTo = Maybe Text
movedTo
            , methodCallable :: Callable
methodCallable = Callable
callable
            }