module Data.GI.CodeGen.Haddock
( deprecatedPragma
, writeDocumentation
, RelativeDocPosition(..)
, writeHaddock
, writeArgDocumentation
, writeReturnDocumentation
, addSectionDocumentation
) where
#if !MIN_VERSION_base(4,13,0)
import Control.Monad (mapM_, unless)
#else
import Control.Monad (unless)
#endif
import qualified Data.Map as M
#if !MIN_VERSION_base(4,11,0)
import Data.Monoid ((<>))
#endif
import qualified Data.Text as T
import Data.Text (Text)
import Data.GI.GIR.Arg (Arg(..))
import Data.GI.GIR.BasicTypes (Name(Name))
import Data.GI.GIR.Callable (Callable(..))
import Data.GI.GIR.Deprecation (DeprecationInfo(..))
import Data.GI.GIR.Documentation (Documentation(..))
import Data.GI.CodeGen.Code (CodeGen, config, line, HaddockSection,
getC2HMap, addSectionFormattedDocs)
import Data.GI.CodeGen.Config (modName, overrides)
import Data.GI.CodeGen.CtoHaskellMap (Hyperlink(..))
import Data.GI.CodeGen.GtkDoc (GtkDoc(..), Token(..), CRef(..), Language(..),
Link(..), ListItem(..), parseGtkDoc)
import Data.GI.CodeGen.Overrides (onlineDocsMap)
import Data.GI.CodeGen.SymbolNaming (lowerSymbol, signalHaskellName,
haddockSignalAnchor)
data RelativeDocPosition = DocBeforeSymbol
| DocAfterSymbol
formatHaddock :: M.Map CRef Hyperlink -> Text -> GtkDoc -> Text
formatHaddock :: Map CRef Hyperlink -> Text -> GtkDoc -> Text
formatHaddock Map CRef Hyperlink
c2h Text
docBase (GtkDoc [Token]
doc) = [Text] -> Text
T.concat ([Text] -> Text) -> [Text] -> Text
forall a b. (a -> b) -> a -> b
$ (Token -> Text) -> [Token] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map Token -> Text
formatToken [Token]
doc
where formatToken :: Token -> Text
formatToken :: Token -> Text
formatToken (Literal Text
l) = Text -> Text
escape Text
l
formatToken (Comment Text
_) = Text
""
formatToken (Verbatim Text
v) = Text
"@" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text -> Text
escape Text
v Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"@"
formatToken (CodeBlock Maybe Language
l Text
c) = Maybe Language -> Text -> Text
formatCodeBlock Maybe Language
l Text
c
formatToken (ExternalLink Link
l) = Link -> Text -> Text
formatLink Link
l Text
docBase
formatToken (Image Link
l) = Link -> Text -> Text
formatImage Link
l Text
docBase
formatToken (SectionHeader Int
l GtkDoc
h) = Map CRef Hyperlink -> Text -> Int -> GtkDoc -> Text
formatSectionHeader Map CRef Hyperlink
c2h Text
docBase Int
l GtkDoc
h
formatToken (List [ListItem]
l) = Map CRef Hyperlink -> Text -> [ListItem] -> Text
formatList Map CRef Hyperlink
c2h Text
docBase [ListItem]
l
formatToken (SymbolRef CRef
cr) = case CRef -> Map CRef Hyperlink -> Maybe Hyperlink
forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup CRef
cr Map CRef Hyperlink
c2h of
Just Hyperlink
hr -> Hyperlink -> Text
formatHyperlink Hyperlink
hr
Maybe Hyperlink
Nothing -> Map CRef Hyperlink -> CRef -> Text
formatUnknownCRef Map CRef Hyperlink
c2h CRef
cr
formatUnknownCRef :: M.Map CRef Hyperlink -> CRef -> Text
formatUnknownCRef :: Map CRef Hyperlink -> CRef -> Text
formatUnknownCRef Map CRef Hyperlink
_ (OldFunctionRef Text
f) = Text -> Text
formatCRef (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ Text
f Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"()"
formatUnknownCRef Map CRef Hyperlink
_ (FunctionRef (Name Text
ns Text
n)) = Text -> Text
formatCRef (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ Text
ns Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"." Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
n
formatUnknownCRef Map CRef Hyperlink
_ (ParamRef Text
p) = Text
"/@" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text -> Text
lowerSymbol Text
p Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"@/"
formatUnknownCRef Map CRef Hyperlink
_ (LocalSignalRef Text
s) =
let sn :: Text
sn = Text -> Text
signalHaskellName Text
s
in Text
"[" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
sn Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"](#" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
haddockSignalAnchor Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
sn Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
")"
formatUnknownCRef Map CRef Hyperlink
c2h (SignalRef owner :: Name
owner@(Name Text
ns Text
n) Text
signal) =
case CRef -> Map CRef Hyperlink -> Maybe Hyperlink
forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup (Name -> CRef
TypeRef Name
owner) Map CRef Hyperlink
c2h of
Maybe Hyperlink
Nothing -> Text -> Text
formatCRef (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ Text
ns Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"." Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
n Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"::" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
signal
Just Hyperlink
r -> Hyperlink -> Text
formatHyperlink Hyperlink
r Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"::" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text -> Text
formatCRef Text
signal
formatUnknownCRef Map CRef Hyperlink
c2h (OldSignalRef Text
owner Text
signal) =
case CRef -> Map CRef Hyperlink -> Maybe Hyperlink
forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup (Text -> CRef
CTypeRef Text
owner) Map CRef Hyperlink
c2h of
Maybe Hyperlink
Nothing -> Text -> Text
formatCRef (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ Text
owner Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"::" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
signal
Just Hyperlink
r -> Hyperlink -> Text
formatHyperlink Hyperlink
r Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"::" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text -> Text
formatCRef Text
signal
formatUnknownCRef Map CRef Hyperlink
c2h (OldPropertyRef Text
owner Text
prop) =
case CRef -> Map CRef Hyperlink -> Maybe Hyperlink
forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup (Text -> CRef
CTypeRef Text
owner) Map CRef Hyperlink
c2h of
Maybe Hyperlink
Nothing -> Text -> Text
formatCRef (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ Text
owner Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
":" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
prop
Just Hyperlink
r -> Hyperlink -> Text
formatHyperlink Hyperlink
r Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
":" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text -> Text
formatCRef Text
prop
formatUnknownCRef Map CRef Hyperlink
c2h (PropertyRef owner :: Name
owner@(Name Text
ns Text
n) Text
prop) =
case CRef -> Map CRef Hyperlink -> Maybe Hyperlink
forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup (Name -> CRef
TypeRef Name
owner) Map CRef Hyperlink
c2h of
Maybe Hyperlink
Nothing -> Text -> Text
formatCRef (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ Text
ns Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"." Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
n Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
":" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
prop
Just Hyperlink
r -> Hyperlink -> Text
formatHyperlink Hyperlink
r Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
":" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text -> Text
formatCRef Text
prop
formatUnknownCRef Map CRef Hyperlink
c2h (VMethodRef Text
owner Text
vmethod) =
case CRef -> Map CRef Hyperlink -> Maybe Hyperlink
forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup (Text -> CRef
CTypeRef Text
owner) Map CRef Hyperlink
c2h of
Maybe Hyperlink
Nothing -> Text -> Text
formatCRef (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ Text
owner Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"." Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
vmethod Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"()"
Just Hyperlink
r -> Hyperlink -> Text
formatHyperlink Hyperlink
r Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"." Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text -> Text
formatCRef Text
vmethod Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"()"
formatUnknownCRef Map CRef Hyperlink
c2h (VFuncRef owner :: Name
owner@(Name Text
ns Text
n) Text
vmethod) =
case CRef -> Map CRef Hyperlink -> Maybe Hyperlink
forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup (Name -> CRef
TypeRef Name
owner) Map CRef Hyperlink
c2h of
Maybe Hyperlink
Nothing -> Text -> Text
formatCRef (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ Text
ns Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"." Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
n Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"." Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
vmethod Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"()"
Just Hyperlink
r -> Hyperlink -> Text
formatHyperlink Hyperlink
r Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"." Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text -> Text
formatCRef Text
vmethod Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"()"
formatUnknownCRef Map CRef Hyperlink
c2h (MethodRef owner :: Name
owner@(Name Text
ns Text
n) Text
method) =
case CRef -> Map CRef Hyperlink -> Maybe Hyperlink
forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup (Name -> CRef
TypeRef Name
owner) Map CRef Hyperlink
c2h of
Maybe Hyperlink
Nothing -> Text -> Text
formatCRef (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ Text
ns Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"." Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
n Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"." Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
method Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"()"
Just Hyperlink
r -> Hyperlink -> Text
formatHyperlink Hyperlink
r Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"." Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text -> Text
formatCRef Text
method Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"()"
formatUnknownCRef Map CRef Hyperlink
c2h (StructFieldRef Text
owner Text
field) =
case CRef -> Map CRef Hyperlink -> Maybe Hyperlink
forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup (Text -> CRef
CTypeRef Text
owner) Map CRef Hyperlink
c2h of
Maybe Hyperlink
Nothing -> Text -> Text
formatCRef (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ Text
owner Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"." Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
field
Just Hyperlink
r -> Hyperlink -> Text
formatHyperlink Hyperlink
r Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"." Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text -> Text
formatCRef Text
field
formatUnknownCRef Map CRef Hyperlink
_ (CTypeRef Text
t) = Text -> Text
formatCRef Text
t
formatUnknownCRef Map CRef Hyperlink
_ (TypeRef (Name Text
ns Text
n)) = Text -> Text
formatCRef (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ Text
ns Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"." Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
n
formatUnknownCRef Map CRef Hyperlink
_ (ConstantRef Text
t) = Text -> Text
formatCRef Text
t
formatCRef :: Text -> Text
formatCRef :: Text -> Text
formatCRef Text
t = Text
"@/" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text -> Text
escape Text
t Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"/@"
formatHyperlink :: Hyperlink -> Text
formatHyperlink :: Hyperlink -> Text
formatHyperlink (TypeIdentifier Text
t) = Text
"t'" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
t Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"'"
formatHyperlink (ValueIdentifier Text
t) = Text
"'" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
t Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"'"
formatHyperlink (ModuleLink Text
m) = Text
"\"" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
m Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"\""
formatHyperlink (ModuleLinkWithAnchor Maybe Text
mLabel Text
m Text
a) =
case Maybe Text
mLabel of
Maybe Text
Nothing -> Text
"\"" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
m Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"#" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
a Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"\""
Just Text
label -> Text
"[" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
label Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"](\"" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
m Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"#" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
a Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"\")"
formatCodeBlock :: Maybe Language -> Text -> Text
formatCodeBlock :: Maybe Language -> Text -> Text
formatCodeBlock Maybe Language
maybeLang Text
code =
let header :: Text
header = case Maybe Language
maybeLang of
Maybe Language
Nothing -> Text
""
Just (Language Text
lang) -> Text
"\n=== /" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
lang Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
" code/\n"
birdTrack :: Text -> Text
birdTrack = [Text] -> Text
T.unlines ([Text] -> Text) -> (Text -> [Text]) -> Text -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Text -> Text) -> [Text] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map (Char -> Text -> Text
T.cons Char
'>') ([Text] -> [Text]) -> (Text -> [Text]) -> Text -> [Text]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> [Text]
T.lines
in Text
header Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text -> Text
birdTrack Text
code
qualifiedWith :: Text -> Text -> Text
qualifiedWith :: Text -> Text -> Text
qualifiedWith Text
address Text
docBase =
if Text
"http://" Text -> Text -> Bool
`T.isPrefixOf` Text
address Bool -> Bool -> Bool
|| Text
"https://" Text -> Text -> Bool
`T.isPrefixOf` Text
address
then Text
address
else if Text
"/" Text -> Text -> Bool
`T.isSuffixOf` Text
docBase
then Text
docBase Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
address
else Text
docBase Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"/" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
address
formatLink :: Link -> Text -> Text
formatLink :: Link -> Text -> Text
formatLink (Link {linkName :: Link -> Text
linkName = Text
name, linkAddress :: Link -> Text
linkAddress = Text
address}) Text
docBase =
let address' :: Text
address' = Text
address Text -> Text -> Text
`qualifiedWith` Text
docBase
name' :: Text
name' = HasCallStack => Text -> Text -> Text -> Text
Text -> Text -> Text -> Text
T.replace Text
">" Text
"\\>" Text
name
in Text
"<" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
address' Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
" " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
name' Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
">"
formatImage :: Link -> Text -> Text
formatImage :: Link -> Text -> Text
formatImage (Link {linkName :: Link -> Text
linkName = Text
name, linkAddress :: Link -> Text
linkAddress = Text
address}) Text
docBase =
let address' :: Text
address' = Text
address Text -> Text -> Text
`qualifiedWith` Text
docBase
name' :: Text
name' = HasCallStack => Text -> Text -> Text -> Text
Text -> Text -> Text -> Text
T.replace Text
">" Text
"\\>" Text
name
in if Text -> Bool
T.null Text
name'
then Text
"<<" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
address' Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
">>"
else Text
"<<" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
address' Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
" " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
name' Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
">>"
formatSectionHeader :: M.Map CRef Hyperlink -> Text -> Int -> GtkDoc -> Text
Map CRef Hyperlink
c2h Text
docBase Int
level GtkDoc
header =
Int -> Text -> Text
T.replicate Int
level Text
"=" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
" " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Map CRef Hyperlink -> Text -> GtkDoc -> Text
formatHaddock Map CRef Hyperlink
c2h Text
docBase GtkDoc
header Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"\n"
formatList :: M.Map CRef Hyperlink -> Text -> [ListItem] -> Text
formatList :: Map CRef Hyperlink -> Text -> [ListItem] -> Text
formatList Map CRef Hyperlink
c2h Text
docBase [ListItem]
items = Text
"\n" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> [Text] -> Text
T.concat ((ListItem -> Text) -> [ListItem] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map ListItem -> Text
formatListItem [ListItem]
items)
where formatListItem :: ListItem -> Text
formatListItem :: ListItem -> Text
formatListItem (ListItem GtkDoc
first [GtkDoc]
rest) =
Text
"* " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> GtkDoc -> Text
format GtkDoc
first Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"\n"
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> [Text] -> Text
T.concat ((GtkDoc -> Text) -> [GtkDoc] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map ((Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"\n") (Text -> Text) -> (GtkDoc -> Text) -> GtkDoc -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GtkDoc -> Text
format) [GtkDoc]
rest)
format :: GtkDoc -> Text
format :: GtkDoc -> Text
format = Map CRef Hyperlink -> Text -> GtkDoc -> Text
formatHaddock Map CRef Hyperlink
c2h Text
docBase
escape :: Text -> Text
escape :: Text -> Text
escape = (Char -> Text) -> Text -> Text
T.concatMap Char -> Text
escapeChar
where
escapeChar :: Char -> Text
escapeChar :: Char -> Text
escapeChar Char
c = if Char
c Char -> [Char] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` ([Char]
"\\/'`\"@<" :: [Char])
then Text
"\\" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Char -> Text
T.singleton Char
c
else Char -> Text
T.singleton Char
c
getDocBase :: CodeGen e Text
getDocBase :: forall e. CodeGen e Text
getDocBase = do
Text
mod <- Config -> Text
modName (Config -> Text)
-> ReaderT
CodeGenConfig (StateT (CGState, ModuleInfo) (Except e)) Config
-> CodeGen e Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReaderT
CodeGenConfig (StateT (CGState, ModuleInfo) (Except e)) Config
forall e. CodeGen e Config
config
Map Text Text
docsMap <- (Overrides -> Map Text Text
onlineDocsMap (Overrides -> Map Text Text)
-> (Config -> Overrides) -> Config -> Map Text Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Config -> Overrides
overrides) (Config -> Map Text Text)
-> ReaderT
CodeGenConfig (StateT (CGState, ModuleInfo) (Except e)) Config
-> ReaderT
CodeGenConfig
(StateT (CGState, ModuleInfo) (Except e))
(Map Text Text)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReaderT
CodeGenConfig (StateT (CGState, ModuleInfo) (Except e)) Config
forall e. CodeGen e Config
config
Text -> CodeGen e Text
forall a.
a
-> ReaderT
CodeGenConfig (StateT (CGState, ModuleInfo) (Except e)) a
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> CodeGen e Text) -> Text -> CodeGen e Text
forall a b. (a -> b) -> a -> b
$ case Text -> Map Text Text -> Maybe Text
forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup Text
mod Map Text Text
docsMap of
Just Text
url -> Text
url
Maybe Text
Nothing -> Text
"http://developer.gnome.org/" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text -> Text
T.toLower Text
mod Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<>
Text
"/stable"
deprecatedPragma :: Text -> Maybe DeprecationInfo -> CodeGen e ()
deprecatedPragma :: forall e. Text -> Maybe DeprecationInfo -> CodeGen e ()
deprecatedPragma Text
_ Maybe DeprecationInfo
Nothing = ()
-> ReaderT
CodeGenConfig (StateT (CGState, ModuleInfo) (Except e)) ()
forall a.
a
-> ReaderT
CodeGenConfig (StateT (CGState, ModuleInfo) (Except e)) a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
deprecatedPragma Text
name (Just DeprecationInfo
info) = do
Map CRef Hyperlink
c2h <- CodeGen e (Map CRef Hyperlink)
forall e. CodeGen e (Map CRef Hyperlink)
getC2HMap
Text
docBase <- CodeGen e Text
forall e. CodeGen e Text
getDocBase
Text
-> ReaderT
CodeGenConfig (StateT (CGState, ModuleInfo) (Except e)) ()
forall e. Text -> CodeGen e ()
line (Text
-> ReaderT
CodeGenConfig (StateT (CGState, ModuleInfo) (Except e)) ())
-> Text
-> ReaderT
CodeGenConfig (StateT (CGState, ModuleInfo) (Except e)) ()
forall a b. (a -> b) -> a -> b
$ Text
"{-# DEPRECATED " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
name Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
" " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<>
([Char] -> Text
T.pack ([Char] -> Text) -> ([Text] -> [Char]) -> [Text] -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Text] -> [Char]
forall a. Show a => a -> [Char]
show) ([Text]
note [Text] -> [Text] -> [Text]
forall a. Semigroup a => a -> a -> a
<> Map CRef Hyperlink -> Text -> [Text]
reason Map CRef Hyperlink
c2h Text
docBase) Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
" #-}"
where reason :: Map CRef Hyperlink -> Text -> [Text]
reason Map CRef Hyperlink
c2h Text
docBase =
case DeprecationInfo -> Maybe Text
deprecationMessage DeprecationInfo
info of
Maybe Text
Nothing -> []
Just Text
msg -> (Text -> Text) -> [Text] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map (Map CRef Hyperlink -> Text -> GtkDoc -> Text
formatHaddock Map CRef Hyperlink
c2h Text
docBase (GtkDoc -> Text) -> (Text -> GtkDoc) -> Text -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> GtkDoc
parseGtkDoc)
(Text -> [Text]
T.lines Text
msg)
note :: [Text]
note = case DeprecationInfo -> Maybe Text
deprecatedSinceVersion DeprecationInfo
info of
Maybe Text
Nothing -> []
Just Text
v -> [Text
"(Since version " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
v Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
")"]
formatDocumentation :: M.Map CRef Hyperlink -> Text -> Documentation -> Text
formatDocumentation :: Map CRef Hyperlink -> Text -> Documentation -> Text
formatDocumentation Map CRef Hyperlink
c2h Text
docBase Documentation
doc = do
let description :: Text
description = case Documentation -> Maybe Text
rawDocText Documentation
doc of
Just Text
raw -> Map CRef Hyperlink -> Text -> GtkDoc -> Text
formatHaddock Map CRef Hyperlink
c2h Text
docBase (Text -> GtkDoc
parseGtkDoc Text
raw)
Maybe Text
Nothing -> Text
"/No description available in the introspection data./"
Text
description Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> case Documentation -> Maybe Text
sinceVersion Documentation
doc of
Maybe Text
Nothing -> Text
""
Just Text
ver -> Text
"\n\n/Since: " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
ver Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"/"
writeDocumentation :: RelativeDocPosition -> Documentation -> CodeGen e ()
writeDocumentation :: forall e. RelativeDocPosition -> Documentation -> CodeGen e ()
writeDocumentation RelativeDocPosition
pos Documentation
doc = do
Map CRef Hyperlink
c2h <- CodeGen e (Map CRef Hyperlink)
forall e. CodeGen e (Map CRef Hyperlink)
getC2HMap
Text
docBase <- CodeGen e Text
forall e. CodeGen e Text
getDocBase
RelativeDocPosition -> Text -> CodeGen e ()
forall e. RelativeDocPosition -> Text -> CodeGen e ()
writeHaddock RelativeDocPosition
pos (Map CRef Hyperlink -> Text -> Documentation -> Text
formatDocumentation Map CRef Hyperlink
c2h Text
docBase Documentation
doc)
writeHaddock :: RelativeDocPosition -> Text -> CodeGen e ()
writeHaddock :: forall e. RelativeDocPosition -> Text -> CodeGen e ()
writeHaddock RelativeDocPosition
pos Text
haddock =
let marker :: Text
marker = case RelativeDocPosition
pos of
RelativeDocPosition
DocBeforeSymbol -> Text
"|"
RelativeDocPosition
DocAfterSymbol -> Text
"^"
lines :: [Text]
lines = case Text -> [Text]
T.lines Text
haddock of
[] -> []
(Text
first:[Text]
rest) -> (Text
"-- " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
marker Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
" " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
first) Text -> [Text] -> [Text]
forall a. a -> [a] -> [a]
: (Text -> Text) -> [Text] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map (Text
"-- " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<>) [Text]
rest
in (Text
-> ReaderT
CodeGenConfig (StateT (CGState, ModuleInfo) (Except e)) ())
-> [Text]
-> ReaderT
CodeGenConfig (StateT (CGState, ModuleInfo) (Except e)) ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ Text
-> ReaderT
CodeGenConfig (StateT (CGState, ModuleInfo) (Except e)) ()
forall e. Text -> CodeGen e ()
line [Text]
lines
writeArgDocumentation :: Arg -> CodeGen e ()
writeArgDocumentation :: forall e. Arg -> CodeGen e ()
writeArgDocumentation Arg
arg =
case Documentation -> Maybe Text
rawDocText (Arg -> Documentation
argDoc Arg
arg) of
Maybe Text
Nothing -> () -> CodeGen e ()
forall a.
a
-> ReaderT
CodeGenConfig (StateT (CGState, ModuleInfo) (Except e)) a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
Just Text
raw -> do
Map CRef Hyperlink
c2h <- CodeGen e (Map CRef Hyperlink)
forall e. CodeGen e (Map CRef Hyperlink)
getC2HMap
Text
docBase <- CodeGen e Text
forall e. CodeGen e Text
getDocBase
let haddock :: Text
haddock = Text
"/@" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text -> Text
lowerSymbol (Arg -> Text
argCName Arg
arg) Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"@/: " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<>
Map CRef Hyperlink -> Text -> GtkDoc -> Text
formatHaddock Map CRef Hyperlink
c2h Text
docBase (Text -> GtkDoc
parseGtkDoc Text
raw)
RelativeDocPosition -> Text -> CodeGen e ()
forall e. RelativeDocPosition -> Text -> CodeGen e ()
writeHaddock RelativeDocPosition
DocAfterSymbol Text
haddock
writeReturnDocumentation :: Callable -> Bool -> CodeGen e ()
writeReturnDocumentation :: forall e. Callable -> Bool -> CodeGen e ()
writeReturnDocumentation Callable
callable Bool
skip = do
Map CRef Hyperlink
c2h <- CodeGen e (Map CRef Hyperlink)
forall e. CodeGen e (Map CRef Hyperlink)
getC2HMap
Text
docBase <- CodeGen e Text
forall e. CodeGen e Text
getDocBase
let returnValInfo :: [Text]
returnValInfo = if Bool
skip
then []
else case Documentation -> Maybe Text
rawDocText (Callable -> Documentation
returnDocumentation Callable
callable) of
Maybe Text
Nothing -> []
Just Text
raw -> [Text
"__Returns:__ " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<>
Map CRef Hyperlink -> Text -> GtkDoc -> Text
formatHaddock Map CRef Hyperlink
c2h Text
docBase
(Text -> GtkDoc
parseGtkDoc Text
raw)]
throwsInfo :: [Text]
throwsInfo = if Callable -> Bool
callableThrows Callable
callable
then [Text
"/(Can throw 'Data.GI.Base.GError.GError')/"]
else []
let fullInfo :: Text
fullInfo = Text -> [Text] -> Text
T.intercalate Text
" " ([Text]
returnValInfo [Text] -> [Text] -> [Text]
forall a. [a] -> [a] -> [a]
++ [Text]
throwsInfo)
Bool -> CodeGen e () -> CodeGen e ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (Text -> Bool
T.null Text
fullInfo) (CodeGen e () -> CodeGen e ()) -> CodeGen e () -> CodeGen e ()
forall a b. (a -> b) -> a -> b
$
RelativeDocPosition -> Text -> CodeGen e ()
forall e. RelativeDocPosition -> Text -> CodeGen e ()
writeHaddock RelativeDocPosition
DocAfterSymbol Text
fullInfo
addSectionDocumentation :: HaddockSection -> Documentation -> CodeGen e ()
addSectionDocumentation :: forall e. HaddockSection -> Documentation -> CodeGen e ()
addSectionDocumentation HaddockSection
section Documentation
doc = do
Map CRef Hyperlink
c2h <- CodeGen e (Map CRef Hyperlink)
forall e. CodeGen e (Map CRef Hyperlink)
getC2HMap
Text
docBase <- CodeGen e Text
forall e. CodeGen e Text
getDocBase
let formatted :: Text
formatted = Map CRef Hyperlink -> Text -> Documentation -> Text
formatDocumentation Map CRef Hyperlink
c2h Text
docBase Documentation
doc
HaddockSection -> Text -> CodeGen e ()
forall e. HaddockSection -> Text -> CodeGen e ()
addSectionFormattedDocs HaddockSection
section Text
formatted