module Data.GI.GIR.Alias
    ( documentListAliases
    ) where

import qualified Data.Map as M
import Data.Maybe (fromMaybe)
import Data.Text (Text)
import qualified Data.Text as T
import Text.XML (Element(elementAttributes), Document(documentRoot))

import Data.GI.GIR.BasicTypes (Alias(..), Type(..), BasicType(..))
import Data.GI.GIR.Type (parseOptionalType)
import Data.GI.GIR.Parser
import Data.GI.GIR.XMLUtils (childElemsWithLocalName)

-- | Find all aliases in a given namespace.
namespaceListAliases :: Element -> M.Map Alias Type
namespaceListAliases :: Element -> Map Alias Type
namespaceListAliases ns :: Element
ns =
    case Name -> Map Name Text -> Maybe Text
forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup "name" (Element -> Map Name Text
elementAttributes Element
ns) of
      Nothing -> [Char] -> Map Alias Type
forall a. HasCallStack => [Char] -> a
error ([Char] -> Map Alias Type) -> [Char] -> Map Alias Type
forall a b. (a -> b) -> a -> b
$ "Namespace with no name!"
      Just nsName :: Text
nsName -> case Text
-> Map Alias Type
-> Element
-> Parser [(Text, Type)]
-> Either Text [(Text, Type)]
forall a.
Text -> Map Alias Type -> Element -> Parser a -> Either Text a
runParser Text
nsName Map Alias Type
forall k a. Map k a
M.empty Element
ns Parser [(Text, Type)]
parseAliases of
                       Left err :: Text
err -> ([Char] -> Map Alias Type
forall a. HasCallStack => [Char] -> a
error ([Char] -> Map Alias Type)
-> (Text -> [Char]) -> Text -> Map Alias Type
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> [Char]
T.unpack) Text
err
                       Right aliases :: [(Text, Type)]
aliases -> [(Alias, Type)] -> Map Alias Type
forall k a. Ord k => [(k, a)] -> Map k a
M.fromList (((Text, Type) -> (Alias, Type))
-> [(Text, Type)] -> [(Alias, Type)]
forall a b. (a -> b) -> [a] -> [b]
map (Text, Type) -> (Alias, Type)
forall b. (Text, b) -> (Alias, b)
addNS [(Text, Type)]
aliases)
                           where addNS :: (Text, b) -> (Alias, b)
addNS (n :: Text
n, t :: b
t) = (Name -> Alias
Alias (Text -> Text -> Name
Name Text
nsName Text
n), b
t)

-- | Parse all the aliases in the current namespace
parseAliases :: Parser [(Text, Type)]
parseAliases :: Parser [(Text, Type)]
parseAliases = Text -> Parser (Text, Type) -> Parser [(Text, Type)]
forall a. Text -> Parser a -> Parser [a]
parseChildrenWithLocalName "alias" Parser (Text, Type)
parseAlias

-- | Parse a single alias
parseAlias :: Parser (Text, Type)
parseAlias :: Parser (Text, Type)
parseAlias = do
  Text
name <- Name -> Parser Text
getAttr "name"
  Maybe Type
t <- Parser (Maybe Type)
parseOptionalType
  (Text, Type) -> Parser (Text, Type)
forall (m :: * -> *) a. Monad m => a -> m a
return (Text
name, Type -> Maybe Type -> Type
forall a. a -> Maybe a -> a
fromMaybe (BasicType -> Type
TBasicType BasicType
TPtr) Maybe Type
t)

-- | Find all aliases in a given document.
documentListAliases :: Document -> M.Map Alias Type
documentListAliases :: Document -> Map Alias Type
documentListAliases doc :: Document
doc = [Map Alias Type] -> Map Alias Type
forall (f :: * -> *) k a.
(Foldable f, Ord k) =>
f (Map k a) -> Map k a
M.unions ((Element -> Map Alias Type) -> [Element] -> [Map Alias Type]
forall a b. (a -> b) -> [a] -> [b]
map Element -> Map Alias Type
namespaceListAliases [Element]
namespaces)
    where namespaces :: [Element]
namespaces = Text -> Element -> [Element]
childElemsWithLocalName "namespace" (Document -> Element
documentRoot Document
doc)