From de73e57a83aace471f594655803e20eaf1027b0b Mon Sep 17 00:00:00 2001 From: David Waern Date: Thu, 22 Jul 2010 19:29:41 +0000 Subject: Solve conflicts --- src/Haddock/Backends/LaTeX.hs | 71 +++++++++++++++++++++---------------------- 1 file changed, 34 insertions(+), 37 deletions(-) (limited to 'src/Haddock/Backends/LaTeX.hs') diff --git a/src/Haddock/Backends/LaTeX.hs b/src/Haddock/Backends/LaTeX.hs index 2981fc4a..b9615fc6 100644 --- a/src/Haddock/Backends/LaTeX.hs +++ b/src/Haddock/Backends/LaTeX.hs @@ -88,6 +88,8 @@ ppLaTeX title packageStr visible_ifaces odir prologue maybe_style libdir ppLaTeXTop title packageStr odir prologue maybe_style visible_ifaces mapM_ (ppLaTeXModule title odir) visible_ifaces + +haddockSty :: FilePath haddockSty = "haddock.sty" @@ -178,7 +180,7 @@ exportListItem (ExportDecl decl _doc subdocs _insts) = ppDocBinder (declName decl) <> case subdocs of [] -> empty - xs -> parens (sep (punctuate comma (map (ppDocBinder . fst) subdocs))) + _ -> parens (sep (punctuate comma (map (ppDocBinder . fst) subdocs))) exportListItem (ExportNoDecl y []) = ppDocBinder y exportListItem (ExportNoDecl y subs) @@ -291,15 +293,25 @@ ppDecl (L loc decl) (mbDoc, fnArgsDoc) instances subdocs = case decl of where unicode = False -ppTyFam _ _ _ _ _ = + +ppTyFam :: Bool -> SrcSpan -> Maybe (Doc DocName) -> + TyClDecl DocName -> Bool -> LaTeX +ppTyFam _ _ _ _ _ = error "type family declarations are currently not supported by --latex" -ppDataInst _ _ _ = + +ppDataInst :: a +ppDataInst = error "data instance declarations are currently not supported by --latex" + +ppTyInst :: Bool -> SrcSpan -> Maybe (Doc DocName) -> + TyClDecl DocName -> Bool -> LaTeX ppTyInst _ _ _ _ _ = error "type instance declarations are currently not supported by --latex" + +ppFor :: SrcSpan -> DocForDecl DocName -> ForeignDecl DocName -> Bool -> LaTeX ppFor _ _ _ _ = error "foreign declarations are currently not supported by --latex" @@ -313,8 +325,7 @@ ppFor _ _ _ _ = ppTySyn :: SrcSpan -> DocForDecl DocName -> TyClDecl DocName -> Bool -> LaTeX ppTySyn loc doc (TySynonym (L _ name) ltyvars _ ltype) unicode - = ppTypeOrFunSig loc name (unLoc ltype) doc - (full, hdr, char '=') unicode False + = ppTypeOrFunSig loc name (unLoc ltype) doc (full, hdr, char '=') unicode where hdr = hsep (keyword "type" : ppDocBinder name : ppTyVars ltyvars) full = hdr <+> char '=' <+> ppLType unicode ltype @@ -341,7 +352,7 @@ ppTypeOrFunSig :: SrcSpan -> DocName -> HsType DocName -> DocForDecl DocName -> (LaTeX, LaTeX, LaTeX) -> Bool -> LaTeX ppTypeOrFunSig _loc _docname typ (doc, argDocs) (pref1, pref2, sep0) - unicode methods + unicode | Map.null argDocs = declWithDoc pref1 (fmap docToLaTeX doc) | otherwise = @@ -458,7 +469,7 @@ ppClassDecl :: [DocInstance DocName] -> SrcSpan -> Maybe (Doc DocName) -> [(DocName, DocForDecl DocName)] -> TyClDecl DocName -> Bool -> LaTeX ppClassDecl instances loc mbDoc subdocs - decl@(ClassDecl lctxt lname ltyvars lfds lsigs _ ats _) unicode + (ClassDecl lctxt lname ltyvars lfds lsigs _ ats _) unicode = declWithDoc classheader (if null body then Nothing else Just (vcat body)) $$ instancesBit where @@ -466,18 +477,16 @@ ppClassDecl instances loc mbDoc subdocs | null lsigs = hdr unicode | otherwise = hdr unicode <+> keyword "where" - nm = unLoc $ tcdLName decl - hdr = ppClassHdr False lctxt (unLoc lname) ltyvars lfds body = catMaybes [fmap docToLaTeX mbDoc, body_] body_ - | null lsigs = Nothing - | otherwise = Just methodTable + | null lsigs, null ats = Nothing + | null ats = Just methodTable +--- | otherwise = atTable $$ methodTable ++ | otherwise = error "LaTeX.ppClassDecl" - | otherwise = error "LaTeX.ppClassDecl" - methodTable = text "\\haddockpremethods{}\\textbf{Methods}" $$ vcat [ ppFunSig loc doc n typ unicode @@ -529,14 +538,13 @@ ppDataDecl :: [DocInstance DocName] -> [(DocName, DocForDecl DocName)] -> SrcSpan -> Maybe (Doc DocName) -> TyClDecl DocName -> Bool -> LaTeX -ppDataDecl instances subdocs loc mbDoc dataDecl unicode +ppDataDecl instances subdocs _loc mbDoc dataDecl unicode = declWithDoc (ppDataHeader dataDecl unicode <+> whereBit) (if null body then Nothing else Just (vcat body)) $$ instancesBit where - docname = unLoc . tcdLName $ dataDecl cons = tcdCons dataDecl resTy = (con_res . unLoc . head) cons @@ -561,11 +569,6 @@ ppDataDecl instances subdocs loc mbDoc dataDecl unicode declWithDoc (vcat (map (ppInstDecl unicode) (map fst instances))) Nothing | otherwise = vcat (map (ppDocInstance unicode) instances) -isRecCon :: Located (ConDecl a) -> Bool -isRecCon lcon = case con_details (unLoc lcon) of - RecCon _ -> True - _ -> False - -- ppConstrHdr is for (non-GADT) existentials constructors' syntax #if __GLASGOW_HASKELL__ == 612 @@ -920,10 +923,6 @@ ppBinder n | isVarSym n = parens $ ppOccName n | otherwise = ppOccName n -ppVerbBinder :: OccName -> LaTeX -ppVerbBinder n - | isVarSym n = parens $ ppVerbOccName n - | otherwise = ppVerbOccName n ppSymName :: Name -> LaTeX ppSymName name @@ -958,14 +957,10 @@ ppLDocName (L _ d) = ppDocName d ppDocBinder :: DocName -> LaTeX ppDocBinder = ppBinder . docNameOcc -ppVerbDocBinder :: DocName -> LaTeX -ppVerbDocBinder = ppVerbBinder . docNameOcc ppName :: Name -> LaTeX ppName = ppOccName . nameOccName -ppVerbName :: Name -> LaTeX -ppVerbName = ppVerbOccName . nameOccName latexFilter :: String -> String latexFilter = foldr latexMunge "" @@ -974,6 +969,8 @@ latexFilter = foldr latexMunge "" latexMonoFilter :: String -> String latexMonoFilter = foldr latexMonoMunge "" + +latexMunge :: Char -> String -> String latexMunge '#' s = "{\\char '43}" ++ s latexMunge '$' s = "{\\char '44}" ++ s latexMunge '%' s = "{\\char '45}" ++ s @@ -988,6 +985,8 @@ latexMunge '[' s = "{\\char 91}" ++ s latexMunge ']' s = "{\\char 93}" ++ s latexMunge c s = c : s + +latexMonoMunge :: Char -> String -> String latexMonoMunge ' ' s = '\\' : ' ' : s latexMonoMunge '\n' s = '\\' : '\\' : s latexMonoMunge c s = latexMunge c s @@ -1006,11 +1005,11 @@ parLatexMarkup ppId isTyCon = Markup { markupString = \s v -> text (fixString v s), markupAppend = \l r v -> l v <> r v, markupIdentifier = markupId, - markupModule = \m v -> let (mdl,_ref) = break (=='#') m in tt (text mdl), + markupModule = \m _ -> let (mdl,_ref) = break (=='#') m in tt (text mdl), markupEmphasis = \p v -> emph (p v), - markupMonospaced = \p v -> tt (p Mono), + markupMonospaced = \p _ -> tt (p Mono), markupUnorderedList = \p v -> itemizedList (map ($v) p) $$ text "", - markupPic = \path v -> parens (text "image: " <> text path), + markupPic = \path _ -> parens (text "image: " <> text path), markupOrderedList = \p v -> enumeratedList (map ($v) p) $$ text "", markupDefList = \l v -> descriptionList (map (\(a,b) -> (a v, b v)) l), markupCodeBlock = \p _ -> quote (verb (p Verb)) $$ text "", @@ -1075,13 +1074,11 @@ latexStripTrailingWhitespace (DocParagraph p) = latexStripTrailingWhitespace p latexStripTrailingWhitespace other = other -latexStripLeadingPara :: Doc a -> Doc a -latexStripLeadingPara (DocParagraph p) = p -latexStripLeadingPara (DocAppend l r) = DocAppend (latexStripLeadingPara l) r -latexStripLeadingPara d = d --- ----------------------------------------------------------------------------- --- LaTeX utils +------------------------------------------------------------------------------- +-- * LaTeX utils +------------------------------------------------------------------------------- + itemizedList :: [LaTeX] -> LaTeX itemizedList items = -- cgit v1.2.3