module Haddock.Backends.Xhtml.DocMarkup (
  docToHtml,
  rdrDocToHtml,
  origDocToHtml,
  docToHtmlNoAnchors,
  docElement, docSection, docSection_,
) where
import Data.List
import Haddock.Backends.Xhtml.Names
import Haddock.Backends.Xhtml.Utils
import Haddock.Types
import Haddock.Utils
import Haddock.Doc (combineDocumentation, emptyMetaDoc,
                    metaDocAppend, metaConcat)
import Text.XHtml hiding ( name, p, quote )
import Data.Maybe (fromMaybe)
import GHC
import Name
parHtmlMarkup :: Qualification -> Bool
              -> (Bool -> a -> Html) -> DocMarkup a Html
parHtmlMarkup qual insertAnchors ppId = Markup {
  markupEmpty                = noHtml,
  markupString               = toHtml,
  markupParagraph            = paragraph,
  markupAppend               = (+++),
  markupIdentifier           = thecode . ppId insertAnchors,
  markupIdentifierUnchecked  = thecode . ppUncheckedLink qual,
  markupModule               = \m -> let (mdl,ref) = break (=='#') m
                                         
                                         
                                         mdl' = case reverse mdl of
                                           '\\':_ -> init mdl
                                           _ -> mdl
                                     in ppModuleRef (mkModuleName mdl') ref,
  markupWarning              = thediv ! [theclass "warning"],
  markupEmphasis             = emphasize,
  markupBold                 = strong,
  markupMonospaced           = thecode,
  markupUnorderedList        = unordList,
  markupOrderedList          = ordList,
  markupDefList              = defList,
  markupCodeBlock            = pre,
  markupHyperlink            = \(Hyperlink url mLabel)
                               -> if insertAnchors
                                  then anchor ! [href url]
                                       << fromMaybe url mLabel
                                  else toHtml $ fromMaybe url mLabel,
  markupAName                = \aname
                               -> if insertAnchors
                                  then namedAnchor aname << ""
                                  else noHtml,
  markupPic                  = \(Picture uri t) -> image ! ([src uri] ++ fromMaybe [] (return . title <$> t)),
  markupMathInline           = \mathjax -> toHtml ("\\(" ++ mathjax ++ "\\)"),
  markupMathDisplay          = \mathjax -> toHtml ("\\[" ++ mathjax ++ "\\]"),
  markupProperty             = pre . toHtml,
  markupExample              = examplesToHtml,
  markupHeader               = \(Header l t) -> makeHeader l t
  }
  where
    makeHeader :: Int -> Html -> Html
    makeHeader 1 mkup = h1 mkup
    makeHeader 2 mkup = h2 mkup
    makeHeader 3 mkup = h3 mkup
    makeHeader 4 mkup = h4 mkup
    makeHeader 5 mkup = h5 mkup
    makeHeader 6 mkup = h6 mkup
    makeHeader l _ = error $ "Somehow got a header level `" ++ show l ++ "' in DocMarkup!"
    examplesToHtml l = pre (concatHtml $ map exampleToHtml l) ! [theclass "screen"]
    exampleToHtml (Example expression result) = htmlExample
      where
        htmlExample = htmlPrompt +++ htmlExpression +++ toHtml (unlines result)
        htmlPrompt = (thecode . toHtml $ ">>> ") ! [theclass "prompt"]
        htmlExpression = (strong . thecode . toHtml $ expression ++ "\n") ! [theclass "userinput"]
data Hack a id =
  UntouchedDoc (MetaDoc a id)
  | CollapsingHeader (Header (DocH a id)) (MetaDoc a id) Int (Maybe String)
  | HackAppend (Hack a id) (Hack a id)
  deriving Eq
toHack :: Int 
              
       -> Maybe String
       
       
       
       
       
       
       
       
       -> [MetaDoc a id] -> Hack a id
toHack _ _ [] = UntouchedDoc emptyMetaDoc
toHack _ _ [x] = UntouchedDoc x
toHack n nm (MetaDoc { _doc = DocHeader (Header l (DocBold x)) }:xs) =
  let 
      h = Header l x
      
      
      p (MetaDoc { _doc = DocHeader (Header l' _) }) = l' > l
      p _ = True
      
      r = takeWhile p xs
      
      r' = drop (length r) xs
      app y [] = y
      app y ys = HackAppend y (toHack (n + 1) nm ys)
  in case r of
      
      [] -> CollapsingHeader h emptyMetaDoc n nm `app` r'
      
      y:ys -> CollapsingHeader h (foldl metaDocAppend y ys) n nm `app` r'
toHack n nm (x:xs) = HackAppend (UntouchedDoc x) (toHack n nm xs)
flatten :: MetaDoc a id -> [MetaDoc a id]
flatten MetaDoc { _meta = m, _doc = DocAppend x y } =
  let f z = MetaDoc { _meta = m, _doc = z }
  in flatten (f x) ++ flatten (f y)
flatten x = [x]
hackMarkup :: DocMarkup id Html -> Hack (ModuleName, OccName) id -> Html
hackMarkup fmt' h' =
  let (html, ms) = hackMarkup' fmt' h'
  in html +++ renderMeta fmt' (metaConcat ms)
  where
    hackMarkup' :: DocMarkup id Html -> Hack (ModuleName, OccName) id
                -> (Html, [Meta])
    hackMarkup' fmt h = case h of
      UntouchedDoc d -> (markup fmt $ _doc d, [_meta d])
      CollapsingHeader (Header lvl titl) par n nm ->
        let id_ = makeAnchorId $ "ch:" ++ fromMaybe "noid:" nm ++ show n
            expanded = False
            col' = collapseControl id_ expanded "caption"
            instTable = (thediv ! collapseSection id_ expanded [] <<)
            lvs = zip [1 .. ] [h1, h2, h3, h4, h5, h6]
            getHeader = fromMaybe caption (lookup lvl lvs)
            subCaption = getHeader ! col' << markup fmt titl
        in ((subCaption +++) . instTable $ markup fmt (_doc par), [_meta par])
      HackAppend d d' -> let (x, m) = hackMarkup' fmt d
                             (y, m') = hackMarkup' fmt d'
                         in (markupAppend fmt x y, m ++ m')
renderMeta :: DocMarkup id Html -> Meta -> Html
renderMeta fmt (Meta { _version = Just x }) =
  markupParagraph fmt . markupEmphasis fmt . toHtml $
    "Since: " ++ formatVersion x
  where
    formatVersion v = concat . intersperse "." $ map show v
renderMeta _ _ = noHtml
markupHacked :: DocMarkup id Html
             -> Maybe String
             -> MDoc id
             -> Html
markupHacked fmt n = hackMarkup fmt . toHack 0 n . flatten
docToHtml :: Maybe String 
                          
          -> Qualification -> MDoc DocName -> Html
docToHtml n qual = markupHacked fmt n . cleanup
  where fmt = parHtmlMarkup qual True (ppDocName qual Raw)
docToHtmlNoAnchors :: Maybe String 
                   -> Qualification -> MDoc DocName -> Html
docToHtmlNoAnchors n qual = markupHacked fmt n . cleanup
  where fmt = parHtmlMarkup qual False (ppDocName qual Raw)
origDocToHtml :: Qualification -> MDoc Name -> Html
origDocToHtml qual = markupHacked fmt Nothing . cleanup
  where fmt = parHtmlMarkup qual True (const $ ppName Raw)
rdrDocToHtml :: Qualification -> MDoc RdrName -> Html
rdrDocToHtml qual = markupHacked fmt Nothing . cleanup
  where fmt = parHtmlMarkup qual True (const ppRdrName)
docElement :: (Html -> Html) -> Html -> Html
docElement el content_ =
  if isNoHtml content_
    then el ! [theclass "doc empty"] << spaceHtml
    else el ! [theclass "doc"] << content_
docSection :: Maybe Name 
           -> Qualification -> Documentation DocName -> Html
docSection n qual = maybe noHtml (docSection_ n qual) . combineDocumentation
docSection_ :: Maybe Name 
            -> Qualification -> MDoc DocName -> Html
docSection_ n qual =
  (docElement thediv <<) . docToHtml (getOccString <$> n) qual
cleanup :: MDoc a -> MDoc a
cleanup = overDoc (markup fmtUnParagraphLists)
  where
    
    
    
    
    
    unParagraph :: Doc a -> Doc a
    unParagraph (DocParagraph d) = d
    unParagraph doc              = doc
    fmtUnParagraphLists :: DocMarkup a (Doc a)
    fmtUnParagraphLists = idMarkup {
      markupUnorderedList = DocUnorderedList . map unParagraph,
      markupOrderedList   = DocOrderedList   . map unParagraph
      }