-- | Parsing of documentation nodes.
module Data.GI.GIR.Documentation
    ( Documentation(..)
    , queryDocumentation
    ) where

import Data.Text (Text)
import Text.XML (Element)

import Data.GI.GIR.XMLUtils (firstChildWithLocalName, getElementContent,
                             lookupAttr)

-- | Documentation for a given element. The documentation text is
-- typically encoded in the gtk-doc format, see
-- https://developer.gnome.org/gtk-doc-manual/ . This can be parsed
-- with `Data.GI.GIR.parseGtkDoc`.
data Documentation = Documentation { Documentation -> Maybe Text
rawDocText   :: Maybe Text
                                   , Documentation -> Maybe Text
sinceVersion :: Maybe Text
                                   } deriving (Int -> Documentation -> ShowS
[Documentation] -> ShowS
Documentation -> String
(Int -> Documentation -> ShowS)
-> (Documentation -> String)
-> ([Documentation] -> ShowS)
-> Show Documentation
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Documentation] -> ShowS
$cshowList :: [Documentation] -> ShowS
show :: Documentation -> String
$cshow :: Documentation -> String
showsPrec :: Int -> Documentation -> ShowS
$cshowsPrec :: Int -> Documentation -> ShowS
Show, Documentation -> Documentation -> Bool
(Documentation -> Documentation -> Bool)
-> (Documentation -> Documentation -> Bool) -> Eq Documentation
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Documentation -> Documentation -> Bool
$c/= :: Documentation -> Documentation -> Bool
== :: Documentation -> Documentation -> Bool
$c== :: Documentation -> Documentation -> Bool
Eq, Eq Documentation
Eq Documentation =>
(Documentation -> Documentation -> Ordering)
-> (Documentation -> Documentation -> Bool)
-> (Documentation -> Documentation -> Bool)
-> (Documentation -> Documentation -> Bool)
-> (Documentation -> Documentation -> Bool)
-> (Documentation -> Documentation -> Documentation)
-> (Documentation -> Documentation -> Documentation)
-> Ord Documentation
Documentation -> Documentation -> Bool
Documentation -> Documentation -> Ordering
Documentation -> Documentation -> Documentation
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Documentation -> Documentation -> Documentation
$cmin :: Documentation -> Documentation -> Documentation
max :: Documentation -> Documentation -> Documentation
$cmax :: Documentation -> Documentation -> Documentation
>= :: Documentation -> Documentation -> Bool
$c>= :: Documentation -> Documentation -> Bool
> :: Documentation -> Documentation -> Bool
$c> :: Documentation -> Documentation -> Bool
<= :: Documentation -> Documentation -> Bool
$c<= :: Documentation -> Documentation -> Bool
< :: Documentation -> Documentation -> Bool
$c< :: Documentation -> Documentation -> Bool
compare :: Documentation -> Documentation -> Ordering
$ccompare :: Documentation -> Documentation -> Ordering
$cp1Ord :: Eq Documentation
Ord)

-- | Parse the documentation node for the given element of the GIR file.
queryDocumentation :: Element -> Documentation
queryDocumentation :: Element -> Documentation
queryDocumentation element :: Element
element = Documentation :: Maybe Text -> Maybe Text -> Documentation
Documentation {
  rawDocText :: Maybe Text
rawDocText = Text -> Element -> Maybe Element
firstChildWithLocalName "doc" Element
element Maybe Element -> (Element -> Maybe Text) -> Maybe Text
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Element -> Maybe Text
getElementContent,
  sinceVersion :: Maybe Text
sinceVersion = Name -> Element -> Maybe Text
lookupAttr "version" Element
element
  }