aboutsummaryrefslogtreecommitdiff
path: root/src/Haddock/Backends/Xhtml/Names.hs
diff options
context:
space:
mode:
authorMark Lentczner <markl@glyphic.com>2010-03-20 22:30:11 +0000
committerMark Lentczner <markl@glyphic.com>2010-03-20 22:30:11 +0000
commit76ca41c4746073c0dc31acd0fb651d06bca4243f (patch)
tree808a6a1d89252c57e343bdcaff52512fc78b7151 /src/Haddock/Backends/Xhtml/Names.hs
parent8771bb0a27598470f034c93128ac6848180f76b1 (diff)
First, experimental XHTML rendering
switch to using the xhtml package copied Html.hs to Xhtml.hs and split into sub-modules under Haddock/Backends/Xhtml and detabify moved footer into div, got ready for iface change headers converted to semantic markup contents in semantic markup summary as semantic markup description in semantic markup, info block in header fixed factored out rendering so during debug it can be readable (see renderToString)
Diffstat (limited to 'src/Haddock/Backends/Xhtml/Names.hs')
-rw-r--r--src/Haddock/Backends/Xhtml/Names.hs76
1 files changed, 76 insertions, 0 deletions
diff --git a/src/Haddock/Backends/Xhtml/Names.hs b/src/Haddock/Backends/Xhtml/Names.hs
new file mode 100644
index 00000000..cbf87c23
--- /dev/null
+++ b/src/Haddock/Backends/Xhtml/Names.hs
@@ -0,0 +1,76 @@
+-----------------------------------------------------------------------------
+-- |
+-- Module : Haddock.Backends.Html.Names
+-- Copyright : (c) Simon Marlow 2003-2006,
+-- David Waern 2006-2009,
+-- Mark Lentczner 2010
+-- License : BSD-like
+--
+-- Maintainer : haddock@projects.haskell.org
+-- Stability : experimental
+-- Portability : portable
+-----------------------------------------------------------------------------
+
+module Haddock.Backends.Xhtml.Names where
+
+import Haddock.Backends.Xhtml.Util
+import Haddock.GhcUtils
+import Haddock.Types
+import Haddock.Utils
+
+import Text.XHtml hiding ( name, title, p, quote )
+
+import GHC
+import Name
+import RdrName
+
+ppOccName :: OccName -> Html
+ppOccName = toHtml . occNameString
+
+ppRdrName :: RdrName -> Html
+ppRdrName = ppOccName . rdrNameOcc
+
+ppLDocName :: Located DocName -> Html
+ppLDocName (L _ d) = ppDocName d
+
+ppDocName :: DocName -> Html
+ppDocName (Documented name mdl) =
+ linkIdOcc mdl (Just occName) << ppOccName occName
+ where occName = nameOccName name
+ppDocName (Undocumented name) = toHtml (getOccString name)
+
+linkTarget :: OccName -> Html
+linkTarget n = namedAnchor (anchorNameStr n) << toHtml ""
+
+ppName :: Name -> Html
+ppName name = toHtml (getOccString name)
+
+
+ppBinder :: Bool -> OccName -> Html
+-- The Bool indicates whether we are generating the summary, in which case
+-- the binder will be a link to the full definition.
+ppBinder True n = linkedAnchor (anchorNameStr n) << ppBinder' n
+ppBinder False n = linkTarget n +++ bold << ppBinder' n
+
+
+ppBinder' :: OccName -> Html
+ppBinder' n
+ | isVarSym n = parens $ ppOccName n
+ | otherwise = ppOccName n
+
+
+linkId :: Module -> Maybe Name -> Html -> Html
+linkId mdl mbName = linkIdOcc mdl (fmap nameOccName mbName)
+
+
+linkIdOcc :: Module -> Maybe OccName -> Html -> Html
+linkIdOcc mdl mbName = anchor ! [href uri]
+ where
+ uri = case mbName of
+ Nothing -> moduleHtmlFile mdl
+ Just name -> nameHtmlRef mdl name
+
+ppModule :: Module -> String -> Html
+ppModule mdl ref = anchor ! [href ((moduleHtmlFile mdl) ++ ref)]
+ << toHtml (moduleString mdl)
+