module Data.GI.GIR.Parser
    ( Parser
    , ParseError
    , parseError
    , runParser
    , parseName
    , parseDeprecation
    , parseDocumentation
    , parseIntegral
    , parseBool
    , parseChildrenWithLocalName
    , parseAllChildrenWithLocalName
    , parseChildrenWithNSName
    , getAttr
    , getAttrWithNamespace
    , queryAttr
    , queryAttrWithNamespace
    , optionalAttr
    , currentNamespace
    , qualifyName
    , resolveQualifiedTypeName
    
    , Name(..)
    , Element
    , GIRXMLNamespace(..)
    , DeprecationInfo
    , Documentation
    ) where
#if !MIN_VERSION_base(4,8,0)
import Control.Applicative ((<$>))
#endif
import Control.Monad.Except
import Control.Monad.Reader
import Data.Monoid ((<>))
import qualified Data.Map as M
import qualified Data.Text as T
import qualified Data.Text.Read as TR
import Data.Text (Text)
import qualified Text.XML as XML
import Text.XML (Element(elementAttributes))
import Text.Show.Pretty (ppShow)
import Data.GI.GIR.BasicTypes (Name(..), Alias(..), Type(TInterface))
import Data.GI.GIR.Deprecation (DeprecationInfo, queryDeprecated)
import Data.GI.GIR.Documentation (Documentation, queryDocumentation)
import Data.GI.GIR.XMLUtils (localName, GIRXMLNamespace(..),
                        childElemsWithLocalName, childElemsWithNSName,
                        lookupAttr, lookupAttrWithNamespace)
data ParseContext = ParseContext {
      ctxNamespace     :: Text,
      
      
      treePosition     :: [Text],
      
      currentElement   :: Element,
      knownAliases     :: M.Map Alias Type
    } deriving Show
type ParseError = Text
type Parser a = ReaderT ParseContext (Except ParseError) a
parseError :: ParseError -> Parser a
parseError msg = do
  ctx <- ask
  let position = (T.intercalate " / " . reverse . treePosition) ctx
  throwError $ "Error when parsing \"" <> position <> "\": " <> msg <> "\n"
                 <> (T.pack . ppShow . currentElement) ctx
elementDescription :: Element -> Text
elementDescription element =
    case M.lookup "name" (elementAttributes element) of
      Nothing -> localName element
      Just n -> localName element <> " [" <> n <> "]"
nameInCurrentNS :: Text -> Parser Name
nameInCurrentNS n = do
  ctx <- ask
  return $ Name (ctxNamespace ctx) n
currentNamespace :: Parser Text
currentNamespace = ctxNamespace <$> ask
resolveQualifiedTypeName :: Name -> Parser Type
resolveQualifiedTypeName name = do
  ctx <- ask
  case M.lookup (Alias name) (knownAliases ctx) of
    
    
    Just (TInterface n) -> resolveQualifiedTypeName n
    Just t -> return t
    Nothing -> return $ TInterface name
getAttr :: XML.Name -> Parser Text
getAttr attr = do
  ctx <- ask
  case lookupAttr attr (currentElement ctx) of
    Just val -> return val
    Nothing -> parseError $ "Expected attribute \"" <>
               (T.pack . show) attr <> "\" not present."
getAttrWithNamespace :: GIRXMLNamespace -> XML.Name -> Parser Text
getAttrWithNamespace ns attr = do
  ctx <- ask
  case lookupAttrWithNamespace ns attr (currentElement ctx) of
    Just val -> return val
    Nothing -> parseError $ "Expected attribute \"" <>
               (T.pack . show) attr <> "\" in namespace \"" <>
               (T.pack . show) ns <> "\" not present."
queryAttr :: XML.Name -> Parser (Maybe Text)
queryAttr attr = do
  ctx <- ask
  return $ lookupAttr attr (currentElement ctx)
queryAttrWithNamespace :: GIRXMLNamespace -> XML.Name -> Parser (Maybe Text)
queryAttrWithNamespace ns attr = do
  ctx <- ask
  return $ lookupAttrWithNamespace ns attr (currentElement ctx)
optionalAttr :: XML.Name -> a -> (Text -> Parser a) -> Parser a
optionalAttr attr def parser =
    queryAttr attr >>= \case
              Just a -> parser a
              Nothing -> return def
qualifyName :: Text -> Parser Name
qualifyName n = case T.split (== '.') n of
    [ns, name] -> return $ Name ns name
    [name] -> nameInCurrentNS name
    _ -> parseError "Could not understand name"
parseName :: Parser Name
parseName = getAttr "name" >>= qualifyName
parseDeprecation :: Parser (Maybe DeprecationInfo)
parseDeprecation = do
  ctx <- ask
  return $ queryDeprecated (currentElement ctx)
parseDocumentation :: Parser Documentation
parseDocumentation = do
  ctx <- ask
  return $ queryDocumentation (currentElement ctx)
parseIntegral :: Integral a => Text -> Parser a
parseIntegral str =
    case TR.signed TR.decimal str of
      Right (n, r) | T.null r -> return n
      _ -> parseError $ "Could not parse integral value: \"" <> str <> "\"."
parseBool :: Text -> Parser Bool
parseBool "0" = return False
parseBool "1" = return True
parseBool other = parseError $ "Unsupported boolean value: " <> T.pack (show other)
parseChildrenWithLocalName :: Text -> Parser a -> Parser [a]
parseChildrenWithLocalName n parser = do
  ctx <- ask
  let introspectableChildren = filter introspectable
                               (childElemsWithLocalName n (currentElement ctx))
  mapM (withElement parser) introspectableChildren
      where introspectable :: Element -> Bool
            introspectable e = lookupAttr "introspectable" e /= Just "0" &&
                               lookupAttr "shadowed-by" e == Nothing
parseAllChildrenWithLocalName :: Text -> Parser a -> Parser [a]
parseAllChildrenWithLocalName n parser = do
  ctx <- ask
  mapM (withElement parser) (childElemsWithLocalName n (currentElement ctx))
parseChildrenWithNSName :: GIRXMLNamespace -> Text -> Parser a -> Parser [a]
parseChildrenWithNSName ns n parser = do
  ctx <- ask
  let introspectableChildren = filter introspectable
                               (childElemsWithNSName ns n (currentElement ctx))
  mapM (withElement parser) introspectableChildren
      where introspectable :: Element -> Bool
            introspectable e = lookupAttr "introspectable" e /= Just "0"
withElement :: Parser a -> Element -> Parser a
withElement parser element = local modifyParsePosition parser
    where modifyParsePosition ctx =
              ctx { treePosition = elementDescription element : treePosition ctx
                  , currentElement = element}
runParser :: Text -> M.Map Alias Type -> Element -> Parser a ->
             Either ParseError a
runParser ns aliases element parser =
    runExcept (runReaderT parser ctx)
              where ctx = ParseContext {
                            ctxNamespace = ns
                          , treePosition = [elementDescription element]
                          , currentElement = element
                          , knownAliases = aliases
                          }