module HaddockHH2(ppHH2Contents, ppHH2Index, ppHH2Files, ppHH2Collection) where
import HsSyn hiding(Doc)
#if __GLASGOW_HASKELL__ < 503
import Pretty
import FiniteMap
#else
import Text.PrettyPrint
import Data.FiniteMap
import Data.List
import Data.Char
#endif
import HaddockModuleTree
import HaddockUtil
import HaddockTypes
ppHH2Contents :: FilePath -> String -> [(Module,Interface)] -> IO ()
ppHH2Contents odir package ifaces = do
  let 	
	contentsHH2File = package++".HxT"
	tree = mkModuleTree (map (\(mod,_) -> (mod,Nothing)) ifaces) --TODO: packages
	doc  =
		text "" $$
		text "" $$
		text "" $$
		nest 4 (ppModuleTree [] tree) $$
		text ""
  writeFile (odir ++ pathSeparator:contentsHH2File) (render doc)
  where
	ppModuleTree :: [String] -> [ModuleTree] -> Doc
	ppModuleTree ss [x]    = ppNode ss x
	ppModuleTree ss (x:xs) = ppNode ss x $$ ppModuleTree ss xs
	ppModuleTree _  []     = error "HaddockHH2.ppHH2Contents.ppModuleTree: no module trees given"
	ppNode :: [String] -> ModuleTree -> Doc
	ppNode ss (Node s leaf _pkg []) =
	  text " ppAttributes leaf (s:ss) <> text "/>"
	ppNode ss (Node s leaf _pkg ts) =
	  text " ppAttributes leaf (s:ss) <> text ">" $$
	  nest 4 (ppModuleTree (s:ss) ts) $+$
	  text ""
			
	ppAttributes :: Bool -> [String] -> Doc
	ppAttributes isleaf ss = hsep [ppId,ppTitle,ppUrl]
	  where
	    mdl = foldr (++) "" (s' : map ('.':) ss')
	    (s':ss') = reverse ss
	                -- reconstruct the module name
	    
	    ppId = text "Id=" <> doubleQuotes (text mdl)
	    
	    ppTitle = text "Title=" <> doubleQuotes (text (head ss))
	    
	    ppUrl | isleaf    = text " Url=" <> doubleQuotes (text (moduleHtmlFile "" mdl))
	          | otherwise = empty
-----------------------------------------------------------------------------------
ppHH2Index :: FilePath -> String -> [(Module,Interface)] -> IO ()
ppHH2Index odir package ifaces = do
  let 
	indexKHH2File     = package++"K.HxK"
	indexNHH2File     = package++"N.HxK"
	docK = 
		text "" $$
		text "" $$
		text "" $$
		nest 4 (ppList index) $+$
		text ""  
	docN = 
		text "" $$
		text "" $$
		text "" $$
		text "" $$
		nest 4 (text "") $$
		text "" $$
		text ""
  writeFile (odir ++ pathSeparator:indexKHH2File) (render docK)
  writeFile (odir ++ pathSeparator:indexNHH2File) (render docN)
  where	
	index :: [(HsName, [Module])]
	index = fmToList (foldr getIfaceIndex emptyFM ifaces)
	getIfaceIndex (mdl,iface) fm =
	    addListToFM_C (++) fm [(name, [mdl]) | (name, Qual mdl' _) <- fmToList (iface_env iface), mdl == mdl']
	
	ppList [] = empty
	ppList ((name,mdls):vs)  =
		text " text (escapeStr (show name)) <> text "\">" $$
		nest 4 (vcat (map (ppJump name) mdls)) $$
		text "" $$
		ppList vs
	ppJump name (Module mdl) = text " text (nameHtmlRef fp mdl name) <> text "\"/>"
	  where
	    fp = case lookupFM html_xrefs (Module mdl) of
	      Nothing  -> ""
	      Just fp0 -> fp0
-----------------------------------------------------------------------------------
ppHH2Files :: FilePath -> String -> [(Module,Interface)] -> IO ()
ppHH2Files odir package ifaces = do
  let filesHH2File = package++".HxF"
      doc =
        text "" $$
        text "" $$
        text "" $$
        nest 4 (ppMods ifaces $$
                text "" $$
                text "" $$
                ppIndexFiles chars $$
                text "text cssFile  <>text "\"/>") $$
                text "text iconFile <>text "\"/>" $$
                text "text jsFile   <>text "\"/>" $$
                text "text plusFile <>text "\"/>" $$
                text "text minusFile<>text "\"/>" $$
        text ""
  writeFile (odir ++ pathSeparator:filesHH2File) (render doc)
  where
    ppMods [] = empty
    ppMods ((Module mdl,_):ifaces) =
		text " text (moduleHtmlFile "" mdl) <> text "\"/>" $$
		ppMods ifaces
		
    ppIndexFiles []     = empty
    ppIndexFiles (c:cs) =
        text " char c <> text ".html\"/>" $$
        ppIndexFiles cs
	
    chars :: [Char]
    chars = keysFM (foldr getIfaceIndex emptyFM ifaces)
    getIfaceIndex (mdl,iface) fm =
        addListToFM fm [(toUpper (head (show name)),()) | (name, Qual mdl' _) <- fmToList (iface_env iface), mdl == mdl']
-----------------------------------------------------------------------------------
ppHH2Collection :: FilePath -> String -> [(Module,Interface)] -> IO ()
ppHH2Collection odir package ifaces = do
  let 
	collectionHH2File = package++".HxC"
	
	doc =
		text "" $$
		text "" $$
		text " text package <> text "\">" $$
		nest 4 (text "" $$
		        nest 4 (text " text package <> text ".HxF\"/>") $$
		        text "" $$
		        text " text package <> text ".HxT\"/>" $$
		        text " text package <> text "K.HxK\"/>" $$
		        text " text package <> text "N.HxK\"/>" $$
		        text "" $$
		        text "" $$
		        text "" $$
		        text "" $$
		        text "" $$
		        text "") $$
		text ""
  writeFile (odir ++ pathSeparator:collectionHH2File) (render doc)