diff options
94 files changed, 4101 insertions, 104 deletions
diff --git a/.gitignore b/.gitignore new file mode 100644 index 00000000..fdf5086a --- /dev/null +++ b/.gitignore @@ -0,0 +1,5 @@ +/dist/ +/tests/html-tests/output/ +/tests/html-tests/tests/doc-index.html.ref +/tests/html-tests/tests/index-frames.html.ref +/tests/html-tests/tests/index.html.ref @@ -1,3 +1,19 @@ +Changes in version 2.10.0 + + * Require GHC >= 7.4 + + * Safe Haskell indications on module pages + + * Type declarations on identifiers no longer necessary + + * Add flag --interface-version + + * Warn when comment refers to in-scope identifier without documentation + + * Bug fix: links to out-of-scope things (#78) + + * Bug fix: module references to other packages work again + Changes in version 2.9.4 * Require GHC >= 7.2 diff --git a/haddock.cabal b/haddock.cabal index 3f186299..84d3c2a8 100644 --- a/haddock.cabal +++ b/haddock.cabal @@ -91,7 +91,7 @@ executable haddock array, xhtml >= 3000.2 && < 3000.3, Cabal >= 1.10, - ghc >= 7.2 && < 7.6 + ghc >= 7.4 && < 7.6 if flag(in-ghc-tree) cpp-options: -DIN_GHC_TREE @@ -153,7 +153,7 @@ library array, xhtml >= 3000.2 && < 3000.3, Cabal >= 1.10, - ghc >= 7.2 && < 7.6 + ghc >= 7.4 && < 7.6 if flag(in-ghc-tree) cpp-options: -DIN_GHC_TREE diff --git a/html/Classic.theme/xhaddock.css b/html/Classic.theme/xhaddock.css index d6b58d22..40ea0d06 100644 --- a/html/Classic.theme/xhaddock.css +++ b/html/Classic.theme/xhaddock.css @@ -488,6 +488,6 @@ td.rdoc p { background: inherit; } - - - +.warning { + color: red; +} diff --git a/html/Ocean.std-theme/ocean.css b/html/Ocean.std-theme/ocean.css index e0ba8b0c..42238709 100644 --- a/html/Ocean.std-theme/ocean.css +++ b/html/Ocean.std-theme/ocean.css @@ -429,6 +429,10 @@ div#style-menu-holder { padding-left: 2em; } +.warning { + color: red; +} + .arguments { margin-top: -0.4em; } diff --git a/src/.ghci b/src/.ghci new file mode 100644 index 00000000..f00e6d55 --- /dev/null +++ b/src/.ghci @@ -0,0 +1 @@ +:set -i../dist/build/autogen -i../dist/build/haddock/haddock-tmp/ -packageghc -optP-include -optP../dist/build/autogen/cabal_macros.h -XCPP -XDeriveDataTypeable -XScopedTypeVariables -XMagicHash diff --git a/src/Haddock/Backends/Hoogle.hs b/src/Haddock/Backends/Hoogle.hs index 6e3e306a..cbb5921d 100644 --- a/src/Haddock/Backends/Hoogle.hs +++ b/src/Haddock/Backends/Hoogle.hs @@ -235,6 +235,7 @@ markupTag = Markup { markupIdentifier = box (TagInline "a") . str . out, markupIdentifierUnchecked = box (TagInline "a") . str . out . snd, markupModule = box (TagInline "a") . str, + markupWarning = box (TagInline "i"), markupEmphasis = box (TagInline "i"), markupMonospaced = box (TagInline "tt"), markupPic = const $ str " ", diff --git a/src/Haddock/Backends/LaTeX.hs b/src/Haddock/Backends/LaTeX.hs index e0a530be..ffe507ab 100644 --- a/src/Haddock/Backends/LaTeX.hs +++ b/src/Haddock/Backends/LaTeX.hs @@ -1006,6 +1006,7 @@ parLatexMarkup ppId = Markup { markupIdentifier = markupId ppId, markupIdentifierUnchecked = markupId (ppVerbOccName . snd), markupModule = \m _ -> let (mdl,_ref) = break (=='#') m in tt (text mdl), + markupWarning = \p v -> emph (p v), markupEmphasis = \p v -> emph (p v), markupMonospaced = \p _ -> tt (p Mono), markupUnorderedList = \p v -> itemizedList (map ($v) p) $$ text "", diff --git a/src/Haddock/Backends/Xhtml/Decl.hs b/src/Haddock/Backends/Xhtml/Decl.hs index 686e9a3e..930a81bf 100644 --- a/src/Haddock/Backends/Xhtml/Decl.hs +++ b/src/Haddock/Backends/Xhtml/Decl.hs @@ -37,7 +37,6 @@ import Name import BasicTypes ( ipNameName ) --- TODO: use DeclInfo DocName or something ppDecl :: Bool -> LinksInfo -> LHsDecl DocName -> DocForDecl DocName -> [DocInstance DocName] -> [(DocName, DocForDecl DocName)] -> Bool -> Qualification -> Html diff --git a/src/Haddock/Backends/Xhtml/DocMarkup.hs b/src/Haddock/Backends/Xhtml/DocMarkup.hs index f506d2b8..ee0a549f 100644 --- a/src/Haddock/Backends/Xhtml/DocMarkup.hs +++ b/src/Haddock/Backends/Xhtml/DocMarkup.hs @@ -39,6 +39,7 @@ parHtmlMarkup qual ppId = Markup { markupIdentifierUnchecked = thecode . ppUncheckedLink qual, markupModule = \m -> let (mdl,ref) = break (=='#') m in ppModuleRef (mkModuleName mdl) ref, + markupWarning = thediv ! [theclass "warning"], markupEmphasis = emphasize, markupMonospaced = thecode, markupUnorderedList = unordList, diff --git a/src/Haddock/Interface/Create.hs b/src/Haddock/Interface/Create.hs index 580aaa83..06d97265 100644 --- a/src/Haddock/Interface/Create.hs +++ b/src/Haddock/Interface/Create.hs @@ -34,7 +34,9 @@ import GHC hiding (flags) import HscTypes import Name import Bag -import RdrName (GlobalRdrEnv) +import RdrName +import TcRnTypes (tcg_warns) +import FastString (unpackFS) -- | Use a 'TypecheckedModule' to produce an 'Interface'. @@ -49,6 +51,7 @@ createInterface tm flags modMap instIfaceMap = do dflags = ms_hspp_opts ms instances = modInfoInstances mi exportedNames = modInfoExports mi + warnings = tcg_warns . fst . tm_internals_ $ tm -- The renamed source should always be available to us, but it's best -- to be on the safe side. @@ -68,16 +71,21 @@ createInterface tm flags modMap instIfaceMap = do | Flag_IgnoreAllExports `elem` flags = OptIgnoreExports : opts0 | otherwise = opts0 - (info, mbDoc) <- liftErrMsg $ lexParseRnHaddockModHeader dflags gre mayDocHeader + (info, mbDoc) <- do + (i, d) <- liftErrMsg $ lexParseRnHaddockModHeader dflags gre mayDocHeader + return (i, addModuleWarning warnings d) let declsWithDocs = topDecls group_ (decls, _) = unzip declsWithDocs localInsts = filter (nameIsLocalOrFrom mdl . getName) instances - maps@(docMap, argMap, subMap, declMap) <- + (docMap0, argMap, subMap, declMap) <- liftErrMsg $ mkMaps dflags gre localInsts exportedNames declsWithDocs - let exports0 = fmap (reverse . map unLoc) mayExports + let docMap = addWarnings warnings gre exportedNames docMap0 + maps = (docMap, argMap, subMap, declMap) + + exports0 = fmap (reverse . map unLoc) mayExports exports | OptIgnoreExports `elem` opts = Nothing | otherwise = exports0 @@ -90,18 +98,16 @@ createInterface tm flags modMap instIfaceMap = do let visibleNames = mkVisibleNames exportItems opts -- Measure haddock documentation coverage. - let - prunedExportItems0 = pruneExportItems exportItems - haddockable = 1 + length exportItems -- module + exports - haddocked = (if isJust mbDoc then 1 else 0) + length prunedExportItems0 - coverage = (haddockable, haddocked) + let prunedExportItems0 = pruneExportItems exportItems + haddockable = 1 + length exportItems -- module + exports + haddocked = (if isJust mbDoc then 1 else 0) + length prunedExportItems0 + coverage = (haddockable, haddocked) -- Prune the export list to just those declarations that have -- documentation, if the 'prune' option is on. - let - prunedExportItems - | OptPrune `elem` opts = prunedExportItems0 - | otherwise = exportItems + let prunedExportItems + | OptPrune `elem` opts = prunedExportItems0 + | otherwise = exportItems return Interface { ifaceMod = mdl, @@ -126,6 +132,40 @@ createInterface tm flags modMap instIfaceMap = do ------------------------------------------------------------------------------- +-- Warnings +------------------------------------------------------------------------------- + + +-- | Add warnings to documentation. If there is a warning for an identifier +-- with no documentation, create a piece of documentation that just contains +-- the warning. +addWarnings :: Warnings -> GlobalRdrEnv -> [Name] -> DocMap Name -> DocMap Name +addWarnings NoWarnings _ _ dm = dm +addWarnings (WarnAll _) _ _ dm = dm +addWarnings (WarnSome ws) gre exps dm = M.unionWith (flip mappend) dm wm + where + wm = M.fromList + [ (n, warnToDoc w) | (occ, w) <- ws, elt <- lookupGlobalRdrEnv gre occ + , let n = gre_name elt, n `elem` exps ] + + +addModuleWarning :: Warnings -> Maybe (Doc id) -> Maybe (Doc id) +addModuleWarning ws = + case ws of + NoWarnings -> id + WarnSome _ -> id + WarnAll w -> let d = warnToDoc w in Just . maybe d (mappend d) + + +warnToDoc :: WarningTxt -> Doc id +warnToDoc w = case w of + (DeprecatedTxt msg) -> format "Deprecated: " msg + (WarningTxt msg) -> format "Warning: " msg + where + format x xs = DocWarning . DocParagraph . DocString . concat $ x : map unpackFS xs + + +------------------------------------------------------------------------------- -- Doc options -- -- Haddock options that are embedded in the source file @@ -160,43 +200,44 @@ parseOption other = tell ["Unrecognised option: " ++ other] >> return Nothing type Maps = (DocMap Name, ArgMap Name, SubMap, DeclMap) -mkMaps :: DynFlags -> GlobalRdrEnv -> [Instance] -> [Name] -> [(LHsDecl Name, [HsDocString])] -> ErrMsgM Maps +mkMaps :: DynFlags + -> GlobalRdrEnv + -> [Instance] + -> [Name] + -> [(LHsDecl Name, [HsDocString])] + -> ErrMsgM Maps mkMaps dflags gre instances exports decls = do - maps <- mapM f decls - let mergeMaps (a,b,c,d) (x,y,z,w) = - (M.unionWith mappend a x, M.unionWith mappend b y, - M.unionWith mappend c z, M.unionWith mappend d w) - let emptyMaps = (M.empty, M.empty, M.empty, M.empty) - return (foldl' mergeMaps emptyMaps maps) + (dm, am, sm, cm) <- unzip4 <$> mapM mappings decls + let f :: (Ord a, Monoid b) => [[(a, b)]] -> Map a b + f = M.fromListWith mappend . concat + return (f dm, f am, f sm, f cm) where - instanceMap = M.fromList [ (getSrcSpan n, n) | i <- instances, let n = getName i ] - - f :: (LHsDecl Name, [HsDocString]) -> ErrMsgM Maps - f (decl@(L _ d), docs) = do - mayDoc <- lexParseRnHaddockCommentList dflags NormalHaddockComment gre docs - argDocs <- fmap (M.mapMaybe id) $ Traversable.forM (typeDocs d) $ - \doc -> lexParseRnHaddockComment dflags NormalHaddockComment gre doc + mappings (ldecl@(L _ decl), docs) = do + doc <- lexParseRnHaddockCommentList dflags NormalHaddockComment gre docs + argDocs <- fmap (M.mapMaybe id) $ Traversable.forM (typeDocs decl) $ + lexParseRnHaddockComment dflags NormalHaddockComment gre - let subs_ = subordinates d - let subs_' = filter (\(name, _, _) -> name `elem` exports) subs_ + let subs = [ s | s@(n, _, _) <- subordinates decl, n `elem` exports ] - (subDocs, subArgMap) <- unzip <$> (forM subs_' $ \(name, mbSubDocStr, subFnArgsDocStr) -> do + (subDocs, subArgMap) <- unzip <$> (forM subs $ \(n, mbSubDocStr, subFnArgsDocStr) -> do mbSubDoc <- lexParseRnHaddockCommentList dflags NormalHaddockComment gre mbSubDocStr subFnArgsDoc <- fmap (M.mapMaybe id) $ Traversable.forM subFnArgsDocStr $ - \doc -> lexParseRnHaddockComment dflags NormalHaddockComment gre doc - return ((name, mbSubDoc), (name, subFnArgsDoc))) + lexParseRnHaddockComment dflags NormalHaddockComment gre + return ((n, mbSubDoc), (n, subFnArgsDoc))) - let subNames = map fst subDocs + let names = case decl of + -- See note [2]. + InstD (InstDecl (L l _) _ _ _) -> maybeToList (M.lookup l instanceMap) + _ -> filter (`elem` exports) (getMainDeclBinder decl) - let names = case d of - InstD (InstDecl (L l _) _ _ _) -> maybeToList (M.lookup l instanceMap) -- See note [2]. - _ -> filter (`elem` exports) (getMainDeclBinder d) + let subNames = map fst subDocs + dm = [ (n, d) | (n, Just d) <- (zip names (repeat doc)) ++ subDocs ] + am = [ (n, argDocs) | n <- names ] ++ subArgMap + sm = [ (n, subNames) | n <- names ] + cm = [ (n, [ldecl]) | n <- names ++ subNames ] + return (dm, am, sm, cm) - let docMap' = M.fromList (mapMaybe (\(n,doc) -> fmap (n,) doc) ([ (n, mayDoc) | n <- names ] ++ subDocs)) - let argMap' = M.fromList [ (n, argDocs) | n <- names ] `mappend` M.fromList subArgMap - let subMap' = M.fromList [ (n, subNames) | n <- names ] - let dclMap' = M.fromList [ (n, [decl]) | n <- names ++ subNames ] - return (docMap', argMap', subMap', dclMap') + instanceMap = M.fromList [ (getSrcSpan n, n) | i <- instances, let n = getName i ] -- Note [2]: @@ -393,18 +434,10 @@ mkExportItems (maps@(docMap, argMap, subMap, declMap)) optExports _ instIfaceMap dflags = case optExports of Nothing -> fullModuleContents dflags gre maps decls - Just exports -> liftM (nubBy commaDeclared . concat) $ mapM lookupExport exports + Just exports -> liftM concat $ mapM lookupExport exports where decls = filter (not . isInstD . unLoc) decls0 - -- A type signature can have multiple names, like: - -- foo, bar :: Types.. - -- When going throug the exported names we have to take care to detect such - -- situations and remove the duplicates. - commaDeclared (ExportDecl (L _ sig1) _ _ _) (ExportDecl (L _ sig2) _ _ _) = - getMainDeclBinder sig1 == getMainDeclBinder sig2 - commaDeclared _ _ = False - lookupExport (IEVar x) = declWith x lookupExport (IEThingAbs t) = declWith t @@ -433,13 +466,12 @@ mkExportItems declWith :: Name -> ErrMsgGhc [ ExportItem Name ] declWith t = - let (doc, subs) = exportDecl t docMap argMap subMap in case findDecl t of - [L _ (ValD _)] -> do + ([L _ (ValD _)], (doc, _)) -> do -- Top-level binding without type signature export <- hiValExportItem t doc return [export] - ds | decl : _ <- filter (not . isValD . unLoc) ds -> + (ds, docs_) | decl : _ <- filter (not . isValD . unLoc) ds -> let declNames = getMainDeclBinder (unL decl) in case () of _ @@ -461,21 +493,20 @@ mkExportItems return [] -- normal case - | otherwise -> return [ mkExportDecl t newDecl (doc, subs) ] + | otherwise -> return [ mkExportDecl t newDecl docs_ ] where - -- Since a single signature might refer to many names, we - -- need to filter the ones that are actually exported. This - -- requires modifying the type signatures to "hide" the - -- names that are not exported. + -- A single signature might refer to many names, but we + -- create an export item for a single name only. So we + -- modify the signature to contain only that single name. newDecl = case decl of (L loc (SigD sig)) -> - L loc . SigD . fromJust $ filterSigNames isExported sig + L loc . SigD . fromJust $ filterSigNames (== t) sig -- fromJust is safe since we already checked in guards -- that 't' is a name declared in this declaration. _ -> decl -- Declaration from another package - [] -> do + ([], _) -> do mayDecl <- hiDecl t case mayDecl of Nothing -> return [ ExportNoDecl t [] ] @@ -489,7 +520,7 @@ mkExportItems let subs_ = [ (n, noDocForDecl) | (n, _, _) <- subordinates (unLoc decl) ] return [ mkExportDecl t decl (noDocForDecl, subs_) ] Just iface -> do - return [ mkExportDecl t decl (exportDecl t (instDocMap iface) (instArgMap iface) (instSubMap iface)) ] + return [ mkExportDecl t decl (lookupDocs t (instDocMap iface) (instArgMap iface) (instSubMap iface)) ] _ -> return [] @@ -506,13 +537,15 @@ mkExportItems isExported = (`elem` exportedNames) - findDecl :: Name -> [LHsDecl Name] - findDecl name - | mdl == thisMod = maybe [] id (M.lookup name declMap) - | Just iface <- M.lookup mdl modMap = maybe [] id (M.lookup name (ifaceDeclMap iface)) - | otherwise = [] + findDecl :: Name -> ([LHsDecl Name], (DocForDecl Name, [(Name, DocForDecl Name)])) + findDecl n + | m == thisMod, Just ds <- M.lookup n declMap = + (ds, lookupDocs n docMap argMap subMap) + | Just iface <- M.lookup m modMap, Just ds <- M.lookup n (ifaceDeclMap iface) = + (ds, lookupDocs n (ifaceDocMap iface) (ifaceArgMap iface) (ifaceSubMap iface)) + | otherwise = ([], (noDocForDecl, [])) where - mdl = nameModule name + m = nameModule n hiDecl :: Name -> ErrMsgGhc (Maybe (LHsDecl Name)) @@ -533,12 +566,14 @@ hiValExportItem name doc = do Just decl -> return (ExportDecl decl doc [] []) -exportDecl :: Name -> DocMap Name -> ArgMap Name -> SubMap -> (DocForDecl Name, [(Name, DocForDecl Name)]) -exportDecl name docMap argMap subMap = - let lookupArgMap x = maybe M.empty id (M.lookup x argMap) in - let doc = (M.lookup name docMap, lookupArgMap name) in - let subs = [ (sub, (M.lookup sub docMap, lookupArgMap sub)) | sub <- maybe [] id (M.lookup name subMap) ] in - (doc, subs) +-- | Lookup docs for a declaration from maps. +lookupDocs :: Name -> DocMap Name -> ArgMap Name -> SubMap -> (DocForDecl Name, [(Name, DocForDecl Name)]) +lookupDocs n docMap argMap subMap = + let lookupArgDoc x = M.findWithDefault M.empty x argMap in + let doc = (M.lookup n docMap, lookupArgDoc n) in + let subs = M.findWithDefault [] n subMap in + let subDocs = [ (s, (M.lookup s docMap, lookupArgDoc s)) | s <- subs ] in + (doc, subDocs) -- | Return all export items produced by an exported module. That is, we're @@ -605,8 +640,21 @@ moduleExports thisMod expMod dflags gre _exports decls ifaceMap instIfaceMap map fullModuleContents :: DynFlags -> GlobalRdrEnv -> Maps -> [LHsDecl Name] -> ErrMsgGhc [ExportItem Name] fullModuleContents dflags gre (docMap, argMap, subMap, declMap) decls = - liftM catMaybes $ mapM mkExportItem decls + liftM catMaybes $ mapM mkExportItem (expandSig decls) where + -- A type signature can have multiple names, like: + -- foo, bar :: Types.. + -- + -- We go through the list of declarations and expand type signatures, so + -- that every type signature has exactly one name! + expandSig :: [LHsDecl name] -> [LHsDecl name] + expandSig = foldr f [] + where + f :: LHsDecl name -> [LHsDecl name] -> [LHsDecl name] + f (L l (SigD (TypeSig names t))) xs = foldr (\n acc -> L l (SigD (TypeSig [n] t)) : acc) xs names + f (L l (SigD (GenericSig names t))) xs = foldr (\n acc -> L l (SigD (GenericSig [n] t)) : acc) xs names + f x xs = x : xs + mkExportItem (L _ (DocD (DocGroup lev docStr))) = do mbDoc <- liftErrMsg $ lexParseRnHaddockComment dflags DocSectionComment gre docStr return $ fmap (ExportGroup lev "") mbDoc @@ -616,12 +664,12 @@ fullModuleContents dflags gre (docMap, argMap, subMap, declMap) decls = mkExportItem (L _ (ValD d)) | name:_ <- collectHsBindBinders d, Just [L _ (ValD _)] <- M.lookup name declMap = -- Top-level binding without type signature. - let (doc, _) = exportDecl name docMap argMap subMap in + let (doc, _) = lookupDocs name docMap argMap subMap in fmap Just (hiValExportItem name doc) | otherwise = return Nothing mkExportItem decl | name:_ <- getMainDeclBinder (unLoc decl) = - let (doc, subs) = exportDecl name docMap argMap subMap in + let (doc, subs) = lookupDocs name docMap argMap subMap in return $ Just (ExportDecl decl doc subs []) | otherwise = return Nothing diff --git a/src/Haddock/Interface/LexParseRn.hs b/src/Haddock/Interface/LexParseRn.hs index f70c5953..ebd2b8fc 100644 --- a/src/Haddock/Interface/LexParseRn.hs +++ b/src/Haddock/Interface/LexParseRn.hs @@ -108,6 +108,7 @@ rename gre = rn a:b:_ | isTyConName a -> DocIdentifier a | otherwise -> DocIdentifier b -- If an id can refer to multiple things, we give precedence to type -- constructors. + DocWarning doc -> DocWarning (rn doc) DocEmphasis doc -> DocEmphasis (rn doc) DocMonospaced doc -> DocMonospaced (rn doc) DocUnorderedList docs -> DocUnorderedList (map rn docs) diff --git a/src/Haddock/Interface/Rename.hs b/src/Haddock/Interface/Rename.hs index 691dafbc..582c2ccd 100644 --- a/src/Haddock/Interface/Rename.hs +++ b/src/Haddock/Interface/Rename.hs @@ -169,6 +169,9 @@ renameDoc d = case d of return (DocIdentifier x') DocIdentifierUnchecked x -> return (DocIdentifierUnchecked x) DocModule str -> return (DocModule str) + DocWarning doc -> do + doc' <- renameDoc doc + return (DocWarning doc') DocEmphasis doc -> do doc' <- renameDoc doc return (DocEmphasis doc') diff --git a/src/Haddock/InterfaceFile.hs b/src/Haddock/InterfaceFile.hs index fcf7fe65..e998ffec 100644 --- a/src/Haddock/InterfaceFile.hs +++ b/src/Haddock/InterfaceFile.hs @@ -65,13 +65,13 @@ binaryInterfaceMagic = 0xD0Cface -- we version our interface files accordingly. binaryInterfaceVersion :: Word16 #if __GLASGOW_HASKELL__ == 702 -binaryInterfaceVersion = 19 +binaryInterfaceVersion = 20 #elif __GLASGOW_HASKELL__ == 703 -binaryInterfaceVersion = 19 +binaryInterfaceVersion = 20 #elif __GLASGOW_HASKELL__ == 704 -binaryInterfaceVersion = 19 +binaryInterfaceVersion = 20 #elif __GLASGOW_HASKELL__ == 705 -binaryInterfaceVersion = 19 +binaryInterfaceVersion = 20 #else #error Unknown GHC version #endif @@ -469,6 +469,9 @@ instance (Binary id) => Binary (Doc id) where put_ bh (DocIdentifierUnchecked x) = do putByte bh 16 put_ bh x + put_ bh (DocWarning ag) = do + putByte bh 17 + put_ bh ag get bh = do h <- getByte bh case h of @@ -523,6 +526,9 @@ instance (Binary id) => Binary (Doc id) where 16 -> do x <- get bh return (DocIdentifierUnchecked x) + 17 -> do + ag <- get bh + return (DocWarning ag) _ -> fail "invalid binary data found" diff --git a/src/Haddock/Types.hs b/src/Haddock/Types.hs index a3a7db15..fe4039a7 100644 --- a/src/Haddock/Types.hs +++ b/src/Haddock/Types.hs @@ -283,6 +283,7 @@ data Doc id | DocIdentifier id | DocIdentifierUnchecked (ModuleName, OccName) | DocModule String + | DocWarning (Doc id) | DocEmphasis (Doc id) | DocMonospaced (Doc id) | DocUnorderedList [Doc id] @@ -324,6 +325,7 @@ data DocMarkup id a = Markup , markupIdentifier :: id -> a , markupIdentifierUnchecked :: (ModuleName, OccName) -> a , markupModule :: String -> a + , markupWarning :: a -> a , markupEmphasis :: a -> a , markupMonospaced :: a -> a , markupUnorderedList :: [a] -> a diff --git a/src/Haddock/Utils.hs b/src/Haddock/Utils.hs index de97ef85..9865fdf1 100644 --- a/src/Haddock/Utils.hs +++ b/src/Haddock/Utils.hs @@ -410,6 +410,7 @@ markup m (DocParagraph d) = markupParagraph m (markup m d) markup m (DocIdentifier x) = markupIdentifier m x markup m (DocIdentifierUnchecked x) = markupIdentifierUnchecked m x markup m (DocModule mod0) = markupModule m mod0 +markup m (DocWarning d) = markupWarning m (markup m d) markup m (DocEmphasis d) = markupEmphasis m (markup m d) markup m (DocMonospaced d) = markupMonospaced m (markup m d) markup m (DocUnorderedList ds) = markupUnorderedList m (map (markup m) ds) @@ -436,6 +437,7 @@ idMarkup = Markup { markupIdentifier = DocIdentifier, markupIdentifierUnchecked = DocIdentifierUnchecked, markupModule = DocModule, + markupWarning = DocWarning, markupEmphasis = DocEmphasis, markupMonospaced = DocMonospaced, markupUnorderedList = DocUnorderedList, diff --git a/tests/html-tests/copy.hs b/tests/html-tests/copy.hs index fe1e5422..188bfd33 100644 --- a/tests/html-tests/copy.hs +++ b/tests/html-tests/copy.hs @@ -7,15 +7,16 @@ import Data.List import Control.Monad +main :: IO () main = do args <- getArgs dir <- getCurrentDirectory contents <- getDirectoryContents (dir </> "output") if not $ null args then - mapM copy [ "output" </> file | file <- contents, ".html" `isSuffixOf` file, takeBaseName file `elem` args ] + mapM_ copy [ "output" </> file | file <- contents, ".html" `isSuffixOf` file, takeBaseName file `elem` args ] else - mapM copy [ "output" </> file | file <- contents, ".html" `isSuffixOf` file ] + mapM_ copy [ "output" </> file | file <- contents, ".html" `isSuffixOf` file ] copy file = do diff --git a/tests/html-tests/tests/A.hs b/tests/html-tests/tests/A.hs index ac8fad49..606b0865 100644 --- a/tests/html-tests/tests/A.hs +++ b/tests/html-tests/tests/A.hs @@ -1,8 +1,17 @@ module A where + data A = A other :: Int other = 2 +-- | Doc for test2 test2 :: Bool test2 = False + +-- | Should show up on the page for both modules A and B +data X = X -- ^ Doc for consructor + +-- | Should show up on the page for both modules A and B +reExport :: Int +reExport = 1 diff --git a/tests/html-tests/tests/A.html.ref b/tests/html-tests/tests/A.html.ref index d5e6dcc0..152dabf7 100644 --- a/tests/html-tests/tests/A.html.ref +++ b/tests/html-tests/tests/A.html.ref @@ -41,6 +41,46 @@ window.onload = function () {pageLoad();setSynopsis("mini_A.html");}; ><p class="caption" >A</p ></div + ><div id="synopsis" + ><p id="control.syn" class="caption expander" onclick="toggleSection('syn')" + >Synopsis</p + ><ul id="section.syn" class="hide" onclick="toggleSection('syn')" + ><li class="src short" + ><span class="keyword" + >data</span + > <a href="" + >A</a + > = <a href="" + >A</a + ></li + ><li class="src short" + ><a href="" + >other</a + > :: <a href="" + >Int</a + ></li + ><li class="src short" + ><a href="" + >test2</a + > :: <a href="" + >Bool</a + ></li + ><li class="src short" + ><span class="keyword" + >data</span + > <a href="" + >X</a + > = <a href="" + >X</a + ></li + ><li class="src short" + ><a href="" + >reExport</a + > :: <a href="" + >Int</a + ></li + ></ul + ></div ><div id="interface" ><h1 >Documentation</h1 @@ -81,6 +121,54 @@ window.onload = function () {pageLoad();setSynopsis("mini_A.html");}; > :: <a href="" >Bool</a ></p + ><div class="doc" + ><p + >Doc for test2 +</p + ></div + ></div + ><div class="top" + ><p class="src" + ><span class="keyword" + >data</span + > <a name="t:X" class="def" + >X</a + > </p + ><div class="doc" + ><p + >Should show up on the page for both modules A and B +</p + ></div + ><div class="subs constructors" + ><p class="caption" + >Constructors</p + ><table + ><tr + ><td class="src" + ><a name="v:X" class="def" + >X</a + ></td + ><td class="doc" + ><p + >Doc for consructor +</p + ></td + ></tr + ></table + ></div + ></div + ><div class="top" + ><p class="src" + ><a name="v:reExport" class="def" + >reExport</a + > :: <a href="" + >Int</a + ></p + ><div class="doc" + ><p + >Should show up on the page for both modules A and B +</p + ></div ></div ></div ></div diff --git a/tests/html-tests/tests/B.hs b/tests/html-tests/tests/B.hs index 28cda4a0..5fd69acd 100644 --- a/tests/html-tests/tests/B.hs +++ b/tests/html-tests/tests/B.hs @@ -1,5 +1,5 @@ -module B ( module A, test ) where -import A ( A(..), test2 ) +module B ( module A, test, reExport, X(..) ) where +import A ( A(..), test2, reExport, X(..) ) -- | This link shouldn't work: 'other'. -- These links should work: 'A.other', 'Data.List.sortBy', 'test2', 'A.test2', 'Data.Maybe.fromMaybe'. diff --git a/tests/html-tests/tests/B.html.ref b/tests/html-tests/tests/B.html.ref index ff8ec91c..ed81cd2a 100644 --- a/tests/html-tests/tests/B.html.ref +++ b/tests/html-tests/tests/B.html.ref @@ -55,6 +55,20 @@ window.onload = function () {pageLoad();setSynopsis("mini_B.html");}; > :: <a href="" >Int</a ></li + ><li class="src short" + ><a href="" + >reExport</a + > :: <a href="" + >Int</a + ></li + ><li class="src short" + ><span class="keyword" + >data</span + > <a href="" + >X</a + > = <a href="" + >X</a + ></li ></ul ></div ><div id="interface" @@ -105,6 +119,49 @@ window.onload = function () {pageLoad();setSynopsis("mini_B.html");}; </p ></div ></div + ><div class="top" + ><p class="src" + ><a name="v:reExport" class="def" + >reExport</a + > :: <a href="" + >Int</a + ></p + ><div class="doc" + ><p + >Should show up on the page for both modules A and B +</p + ></div + ></div + ><div class="top" + ><p class="src" + ><span class="keyword" + >data</span + > <a name="t:X" class="def" + >X</a + > </p + ><div class="doc" + ><p + >Should show up on the page for both modules A and B +</p + ></div + ><div class="subs constructors" + ><p class="caption" + >Constructors</p + ><table + ><tr + ><td class="src" + ><a name="v:X" class="def" + >X</a + ></td + ><td class="doc" + ><p + >Doc for consructor +</p + ></td + ></tr + ></table + ></div + ></div ></div ></div ><div id="footer" diff --git a/tests/html-tests/tests/BugDeprecated.hs b/tests/html-tests/tests/BugDeprecated.hs new file mode 100644 index 00000000..0f7ac2eb --- /dev/null +++ b/tests/html-tests/tests/BugDeprecated.hs @@ -0,0 +1,18 @@ +module BugDeprecated where + +foo, bar, baz :: Int +foo = 23 +bar = 23 +baz = 23 +{-# DEPRECATED foo "for foo" #-} +{-# DEPRECATED bar "for bar" #-} +{-# DEPRECATED baz "for baz" #-} + +-- | some documentation for one, two and three +one, two, three :: Int +one = 23 +two = 23 +three = 23 +{-# DEPRECATED one "for one" #-} +{-# DEPRECATED two "for two" #-} +{-# DEPRECATED three "for three" #-} diff --git a/tests/html-tests/tests/BugDeprecated.html.ref b/tests/html-tests/tests/BugDeprecated.html.ref new file mode 100644 index 00000000..394ce279 --- /dev/null +++ b/tests/html-tests/tests/BugDeprecated.html.ref @@ -0,0 +1,192 @@ +<!DOCTYPE html PUBLIC "-//W3C//DTD XHTML 1.0 Transitional//EN" "http://www.w3.org/TR/xhtml1/DTD/xhtml1-transitional.dtd"> +<html xmlns="http://www.w3.org/1999/xhtml" +><head + ><meta http-equiv="Content-Type" content="text/html; charset=UTF-8" + /><title + >BugDeprecated</title + ><link href="ocean.css" rel="stylesheet" type="text/css" title="Ocean" + /><script src="haddock-util.js" type="text/javascript" + ></script + ><script type="text/javascript" + >//<![CDATA[ +window.onload = function () {pageLoad();setSynopsis("mini_BugDeprecated.html");}; +//]]> +</script + ></head + ><body + ><div id="package-header" + ><ul class="links" id="page-menu" + ><li + ><a href="" + >Contents</a + ></li + ><li + ><a href="" + >Index</a + ></li + ></ul + ><p class="caption" class="empty" + > </p + ></div + ><div id="content" + ><div id="module-header" + ><table class="info" + ><tr + ><th + >Safe Haskell</th + ><td + >None</td + ></tr + ></table + ><p class="caption" + >BugDeprecated</p + ></div + ><div id="synopsis" + ><p id="control.syn" class="caption expander" onclick="toggleSection('syn')" + >Synopsis</p + ><ul id="section.syn" class="hide" onclick="toggleSection('syn')" + ><li class="src short" + ><a href="" + >foo</a + > :: <a href="" + >Int</a + ></li + ><li class="src short" + ><a href="" + >baz</a + > :: <a href="" + >Int</a + ></li + ><li class="src short" + ><a href="" + >bar</a + > :: <a href="" + >Int</a + ></li + ><li class="src short" + ><a href="" + >one</a + > :: <a href="" + >Int</a + ></li + ><li class="src short" + ><a href="" + >three</a + > :: <a href="" + >Int</a + ></li + ><li class="src short" + ><a href="" + >two</a + > :: <a href="" + >Int</a + ></li + ></ul + ></div + ><div id="interface" + ><h1 + >Documentation</h1 + ><div class="top" + ><p class="src" + ><a name="v:foo" class="def" + >foo</a + > :: <a href="" + >Int</a + ></p + ><div class="doc" + ><div class="warning" + ><p + >Deprecated: for foo</p + ></div + ></div + ></div + ><div class="top" + ><p class="src" + ><a name="v:baz" class="def" + >baz</a + > :: <a href="" + >Int</a + ></p + ><div class="doc" + ><div class="warning" + ><p + >Deprecated: for baz</p + ></div + ></div + ></div + ><div class="top" + ><p class="src" + ><a name="v:bar" class="def" + >bar</a + > :: <a href="" + >Int</a + ></p + ><div class="doc" + ><div class="warning" + ><p + >Deprecated: for bar</p + ></div + ></div + ></div + ><div class="top" + ><p class="src" + ><a name="v:one" class="def" + >one</a + > :: <a href="" + >Int</a + ></p + ><div class="doc" + ><div class="warning" + ><p + >Deprecated: for one</p + ></div + ><p + >some documentation for one, two and three +</p + ></div + ></div + ><div class="top" + ><p class="src" + ><a name="v:three" class="def" + >three</a + > :: <a href="" + >Int</a + ></p + ><div class="doc" + ><div class="warning" + ><p + >Deprecated: for three</p + ></div + ><p + >some documentation for one, two and three +</p + ></div + ></div + ><div class="top" + ><p class="src" + ><a name="v:two" class="def" + >two</a + > :: <a href="" + >Int</a + ></p + ><div class="doc" + ><div class="warning" + ><p + >Deprecated: for two</p + ></div + ><p + >some documentation for one, two and three +</p + ></div + ></div + ></div + ></div + ><div id="footer" + ><p + >Produced by <a href="" + >Haddock</a + > version 2.10.0</p + ></div + ></body + ></html +> diff --git a/tests/html-tests/tests/BugExportHeadings.hs b/tests/html-tests/tests/BugExportHeadings.hs new file mode 100644 index 00000000..a5493a08 --- /dev/null +++ b/tests/html-tests/tests/BugExportHeadings.hs @@ -0,0 +1,29 @@ +-- test for #192 +module BugExportHeadings ( +-- * Foo + foo +-- * Bar +, bar +-- * Baz +, baz + +-- * One +, one +-- * Two +, two +-- * Three +, three +) where + +foo, bar, baz :: Int +foo = 23 +bar = 23 +baz = 23 + +one, two, three :: Int +one = 23 +two = 23 +three = 23 +{-# DEPRECATED one "for one" #-} +{-# DEPRECATED two "for two" #-} +{-# DEPRECATED three "for three" #-} diff --git a/tests/html-tests/tests/BugExportHeadings.html.ref b/tests/html-tests/tests/BugExportHeadings.html.ref new file mode 100644 index 00000000..37056334 --- /dev/null +++ b/tests/html-tests/tests/BugExportHeadings.html.ref @@ -0,0 +1,217 @@ +<!DOCTYPE html PUBLIC "-//W3C//DTD XHTML 1.0 Transitional//EN" "http://www.w3.org/TR/xhtml1/DTD/xhtml1-transitional.dtd"> +<html xmlns="http://www.w3.org/1999/xhtml" +><head + ><meta http-equiv="Content-Type" content="text/html; charset=UTF-8" + /><title + >BugExportHeadings</title + ><link href="ocean.css" rel="stylesheet" type="text/css" title="Ocean" + /><script src="haddock-util.js" type="text/javascript" + ></script + ><script type="text/javascript" + >//<![CDATA[ +window.onload = function () {pageLoad();setSynopsis("mini_BugExportHeadings.html");}; +//]]> +</script + ></head + ><body + ><div id="package-header" + ><ul class="links" id="page-menu" + ><li + ><a href="" + >Contents</a + ></li + ><li + ><a href="" + >Index</a + ></li + ></ul + ><p class="caption" class="empty" + > </p + ></div + ><div id="content" + ><div id="module-header" + ><table class="info" + ><tr + ><th + >Safe Haskell</th + ><td + >None</td + ></tr + ></table + ><p class="caption" + >BugExportHeadings</p + ></div + ><div id="table-of-contents" + ><p class="caption" + >Contents</p + ><ul + ><li + ><a href="" + >Foo +</a + ></li + ><li + ><a href="" + >Bar +</a + ></li + ><li + ><a href="" + >Baz +</a + ></li + ><li + ><a href="" + >One +</a + ></li + ><li + ><a href="" + >Two +</a + ></li + ><li + ><a href="" + >Three +</a + ></li + ></ul + ></div + ><div id="synopsis" + ><p id="control.syn" class="caption expander" onclick="toggleSection('syn')" + >Synopsis</p + ><ul id="section.syn" class="hide" onclick="toggleSection('syn')" + ><li class="src short" + ><a href="" + >foo</a + > :: <a href="" + >Int</a + ></li + ><li class="src short" + ><a href="" + >bar</a + > :: <a href="" + >Int</a + ></li + ><li class="src short" + ><a href="" + >baz</a + > :: <a href="" + >Int</a + ></li + ><li class="src short" + ><a href="" + >one</a + > :: <a href="" + >Int</a + ></li + ><li class="src short" + ><a href="" + >two</a + > :: <a href="" + >Int</a + ></li + ><li class="src short" + ><a href="" + >three</a + > :: <a href="" + >Int</a + ></li + ></ul + ></div + ><div id="interface" + ><h1 id="g:1" + >Foo +</h1 + ><div class="top" + ><p class="src" + ><a name="v:foo" class="def" + >foo</a + > :: <a href="" + >Int</a + ></p + ></div + ><h1 id="g:2" + >Bar +</h1 + ><div class="top" + ><p class="src" + ><a name="v:bar" class="def" + >bar</a + > :: <a href="" + >Int</a + ></p + ></div + ><h1 id="g:3" + >Baz +</h1 + ><div class="top" + ><p class="src" + ><a name="v:baz" class="def" + >baz</a + > :: <a href="" + >Int</a + ></p + ></div + ><h1 id="g:4" + >One +</h1 + ><div class="top" + ><p class="src" + ><a name="v:one" class="def" + >one</a + > :: <a href="" + >Int</a + ></p + ><div class="doc" + ><div class="warning" + ><p + >Deprecated: for one</p + ></div + ></div + ></div + ><h1 id="g:5" + >Two +</h1 + ><div class="top" + ><p class="src" + ><a name="v:two" class="def" + >two</a + > :: <a href="" + >Int</a + ></p + ><div class="doc" + ><div class="warning" + ><p + >Deprecated: for two</p + ></div + ></div + ></div + ><h1 id="g:6" + >Three +</h1 + ><div class="top" + ><p class="src" + ><a name="v:three" class="def" + >three</a + > :: <a href="" + >Int</a + ></p + ><div class="doc" + ><div class="warning" + ><p + >Deprecated: for three</p + ></div + ></div + ></div + ></div + ></div + ><div id="footer" + ><p + >Produced by <a href="" + >Haddock</a + > version 2.10.0</p + ></div + ></body + ></html +> diff --git a/tests/html-tests/tests/DeprecatedClass.hs b/tests/html-tests/tests/DeprecatedClass.hs new file mode 100644 index 00000000..018904ab --- /dev/null +++ b/tests/html-tests/tests/DeprecatedClass.hs @@ -0,0 +1,15 @@ +module DeprecatedClass where + +-- | some class +class SomeClass a where + -- | documentation for foo + foo :: a -> a + +{-# DEPRECATED SomeClass "SomeClass" #-} +{-# DEPRECATED foo "foo" #-} + +class SomeOtherClass a where + bar :: a -> a + +{-# DEPRECATED SomeOtherClass "SomeOtherClass" #-} +{-# DEPRECATED bar "bar" #-} diff --git a/tests/html-tests/tests/DeprecatedClass.html.ref b/tests/html-tests/tests/DeprecatedClass.html.ref new file mode 100644 index 00000000..578e8bfb --- /dev/null +++ b/tests/html-tests/tests/DeprecatedClass.html.ref @@ -0,0 +1,157 @@ +<!DOCTYPE html PUBLIC "-//W3C//DTD XHTML 1.0 Transitional//EN" "http://www.w3.org/TR/xhtml1/DTD/xhtml1-transitional.dtd"> +<html xmlns="http://www.w3.org/1999/xhtml" +><head + ><meta http-equiv="Content-Type" content="text/html; charset=UTF-8" + /><title + >DeprecatedClass</title + ><link href="ocean.css" rel="stylesheet" type="text/css" title="Ocean" + /><script src="haddock-util.js" type="text/javascript" + ></script + ><script type="text/javascript" + >//<![CDATA[ +window.onload = function () {pageLoad();setSynopsis("mini_DeprecatedClass.html");}; +//]]> +</script + ></head + ><body + ><div id="package-header" + ><ul class="links" id="page-menu" + ><li + ><a href="" + >Contents</a + ></li + ><li + ><a href="" + >Index</a + ></li + ></ul + ><p class="caption" class="empty" + > </p + ></div + ><div id="content" + ><div id="module-header" + ><table class="info" + ><tr + ><th + >Safe Haskell</th + ><td + >None</td + ></tr + ></table + ><p class="caption" + >DeprecatedClass</p + ></div + ><div id="synopsis" + ><p id="control.syn" class="caption expander" onclick="toggleSection('syn')" + >Synopsis</p + ><ul id="section.syn" class="hide" onclick="toggleSection('syn')" + ><li class="src short" + ><span class="keyword" + >class</span + > <a href="" + >SomeClass</a + > a <span class="keyword" + >where</span + ><ul class="subs" + ><li + ><a href="" + >foo</a + > :: a -> a</li + ></ul + ></li + ><li class="src short" + ><span class="keyword" + >class</span + > <a href="" + >SomeOtherClass</a + > a <span class="keyword" + >where</span + ><ul class="subs" + ><li + ><a href="" + >bar</a + > :: a -> a</li + ></ul + ></li + ></ul + ></div + ><div id="interface" + ><h1 + >Documentation</h1 + ><div class="top" + ><p class="src" + ><span class="keyword" + >class</span + > <a name="t:SomeClass" class="def" + >SomeClass</a + > a <span class="keyword" + >where</span + ></p + ><div class="doc" + ><div class="warning" + ><p + >Deprecated: SomeClass</p + ></div + ><p + >some class +</p + ></div + ><div class="subs methods" + ><p class="caption" + >Methods</p + ><p class="src" + ><a name="v:foo" class="def" + >foo</a + > :: a -> a</p + ><div class="doc" + ><div class="warning" + ><p + >Deprecated: foo</p + ></div + ><p + >documentation for foo +</p + ></div + ></div + ></div + ><div class="top" + ><p class="src" + ><span class="keyword" + >class</span + > <a name="t:SomeOtherClass" class="def" + >SomeOtherClass</a + > a <span class="keyword" + >where</span + ></p + ><div class="doc" + ><div class="warning" + ><p + >Deprecated: SomeOtherClass</p + ></div + ></div + ><div class="subs methods" + ><p class="caption" + >Methods</p + ><p class="src" + ><a name="v:bar" class="def" + >bar</a + > :: a -> a</p + ><div class="doc" + ><div class="warning" + ><p + >Deprecated: bar</p + ></div + ></div + ></div + ></div + ></div + ></div + ><div id="footer" + ><p + >Produced by <a href="" + >Haddock</a + > version 2.10.0</p + ></div + ></body + ></html +> diff --git a/tests/html-tests/tests/DeprecatedData.hs b/tests/html-tests/tests/DeprecatedData.hs new file mode 100644 index 00000000..c40ba122 --- /dev/null +++ b/tests/html-tests/tests/DeprecatedData.hs @@ -0,0 +1,15 @@ +{-# LANGUAGE TypeFamilies #-} +module DeprecatedData where + +-- | type Foo +data Foo = Foo -- ^ constructor Foo + | Bar -- ^ constructor Bar + +{-# DEPRECATED Foo "Foo" #-} +{-# DEPRECATED Bar "Bar" #-} + +data One = One + | Two + +{-# DEPRECATED One "One" #-} +{-# DEPRECATED Two "Two" #-} diff --git a/tests/html-tests/tests/DeprecatedData.html.ref b/tests/html-tests/tests/DeprecatedData.html.ref new file mode 100644 index 00000000..06cc73dc --- /dev/null +++ b/tests/html-tests/tests/DeprecatedData.html.ref @@ -0,0 +1,192 @@ +<!DOCTYPE html PUBLIC "-//W3C//DTD XHTML 1.0 Transitional//EN" "http://www.w3.org/TR/xhtml1/DTD/xhtml1-transitional.dtd"> +<html xmlns="http://www.w3.org/1999/xhtml" +><head + ><meta http-equiv="Content-Type" content="text/html; charset=UTF-8" + /><title + >DeprecatedData</title + ><link href="ocean.css" rel="stylesheet" type="text/css" title="Ocean" + /><script src="haddock-util.js" type="text/javascript" + ></script + ><script type="text/javascript" + >//<![CDATA[ +window.onload = function () {pageLoad();setSynopsis("mini_DeprecatedData.html");}; +//]]> +</script + ></head + ><body + ><div id="package-header" + ><ul class="links" id="page-menu" + ><li + ><a href="" + >Contents</a + ></li + ><li + ><a href="" + >Index</a + ></li + ></ul + ><p class="caption" class="empty" + > </p + ></div + ><div id="content" + ><div id="module-header" + ><table class="info" + ><tr + ><th + >Safe Haskell</th + ><td + >None</td + ></tr + ></table + ><p class="caption" + >DeprecatedData</p + ></div + ><div id="synopsis" + ><p id="control.syn" class="caption expander" onclick="toggleSection('syn')" + >Synopsis</p + ><ul id="section.syn" class="hide" onclick="toggleSection('syn')" + ><li class="src short" + ><span class="keyword" + >data</span + > <a href="" + >Foo</a + > <ul class="subs" + ><li + >= <a href="" + >Foo</a + > </li + ><li + >| <a href="" + >Bar</a + > </li + ></ul + ></li + ><li class="src short" + ><span class="keyword" + >data</span + > <a href="" + >One</a + > <ul class="subs" + ><li + >= <a href="" + >One</a + > </li + ><li + >| <a href="" + >Two</a + > </li + ></ul + ></li + ></ul + ></div + ><div id="interface" + ><h1 + >Documentation</h1 + ><div class="top" + ><p class="src" + ><span class="keyword" + >data</span + > <a name="t:Foo" class="def" + >Foo</a + > </p + ><div class="doc" + ><div class="warning" + ><p + >Deprecated: Foo</p + ></div + ><p + >type Foo +</p + ></div + ><div class="subs constructors" + ><p class="caption" + >Constructors</p + ><table + ><tr + ><td class="src" + ><a name="v:Foo" class="def" + >Foo</a + ></td + ><td class="doc" + ><div class="warning" + ><p + >Deprecated: Foo</p + ></div + ><p + >constructor Foo +</p + ></td + ></tr + ><tr + ><td class="src" + ><a name="v:Bar" class="def" + >Bar</a + ></td + ><td class="doc" + ><div class="warning" + ><p + >Deprecated: Bar</p + ></div + ><p + >constructor Bar +</p + ></td + ></tr + ></table + ></div + ></div + ><div class="top" + ><p class="src" + ><span class="keyword" + >data</span + > <a name="t:One" class="def" + >One</a + > </p + ><div class="doc" + ><div class="warning" + ><p + >Deprecated: One</p + ></div + ></div + ><div class="subs constructors" + ><p class="caption" + >Constructors</p + ><table + ><tr + ><td class="src" + ><a name="v:One" class="def" + >One</a + ></td + ><td class="doc" + ><div class="warning" + ><p + >Deprecated: One</p + ></div + ></td + ></tr + ><tr + ><td class="src" + ><a name="v:Two" class="def" + >Two</a + ></td + ><td class="doc" + ><div class="warning" + ><p + >Deprecated: Two</p + ></div + ></td + ></tr + ></table + ></div + ></div + ></div + ></div + ><div id="footer" + ><p + >Produced by <a href="" + >Haddock</a + > version 2.10.0</p + ></div + ></body + ></html +> diff --git a/tests/html-tests/tests/DeprecatedFunction.hs b/tests/html-tests/tests/DeprecatedFunction.hs new file mode 100644 index 00000000..55416369 --- /dev/null +++ b/tests/html-tests/tests/DeprecatedFunction.hs @@ -0,0 +1,6 @@ +module DeprecatedFunction where + +-- | some documentation foo +foo :: Int +foo = 23 +{-# DEPRECATED foo "use bar instead" #-} diff --git a/tests/html-tests/tests/DeprecatedFunction.html.ref b/tests/html-tests/tests/DeprecatedFunction.html.ref new file mode 100644 index 00000000..25e1863c --- /dev/null +++ b/tests/html-tests/tests/DeprecatedFunction.html.ref @@ -0,0 +1,86 @@ +<!DOCTYPE html PUBLIC "-//W3C//DTD XHTML 1.0 Transitional//EN" "http://www.w3.org/TR/xhtml1/DTD/xhtml1-transitional.dtd"> +<html xmlns="http://www.w3.org/1999/xhtml" +><head + ><meta http-equiv="Content-Type" content="text/html; charset=UTF-8" + /><title + >DeprecatedFunction</title + ><link href="ocean.css" rel="stylesheet" type="text/css" title="Ocean" + /><script src="haddock-util.js" type="text/javascript" + ></script + ><script type="text/javascript" + >//<![CDATA[ +window.onload = function () {pageLoad();setSynopsis("mini_DeprecatedFunction.html");}; +//]]> +</script + ></head + ><body + ><div id="package-header" + ><ul class="links" id="page-menu" + ><li + ><a href="" + >Contents</a + ></li + ><li + ><a href="" + >Index</a + ></li + ></ul + ><p class="caption" class="empty" + > </p + ></div + ><div id="content" + ><div id="module-header" + ><table class="info" + ><tr + ><th + >Safe Haskell</th + ><td + >None</td + ></tr + ></table + ><p class="caption" + >DeprecatedFunction</p + ></div + ><div id="synopsis" + ><p id="control.syn" class="caption expander" onclick="toggleSection('syn')" + >Synopsis</p + ><ul id="section.syn" class="hide" onclick="toggleSection('syn')" + ><li class="src short" + ><a href="" + >foo</a + > :: <a href="" + >Int</a + ></li + ></ul + ></div + ><div id="interface" + ><h1 + >Documentation</h1 + ><div class="top" + ><p class="src" + ><a name="v:foo" class="def" + >foo</a + > :: <a href="" + >Int</a + ></p + ><div class="doc" + ><div class="warning" + ><p + >Deprecated: use bar instead</p + ></div + ><p + >some documentation foo +</p + ></div + ></div + ></div + ></div + ><div id="footer" + ><p + >Produced by <a href="" + >Haddock</a + > version 2.10.0</p + ></div + ></body + ></html +> diff --git a/tests/html-tests/tests/DeprecatedFunction2.hs b/tests/html-tests/tests/DeprecatedFunction2.hs new file mode 100644 index 00000000..bdbbf95c --- /dev/null +++ b/tests/html-tests/tests/DeprecatedFunction2.hs @@ -0,0 +1,6 @@ +module DeprecatedFunction2 where + + +foo :: Int +foo = 23 +{-# DEPRECATED foo "use bar instead" #-} diff --git a/tests/html-tests/tests/DeprecatedFunction2.html.ref b/tests/html-tests/tests/DeprecatedFunction2.html.ref new file mode 100644 index 00000000..ffc69f83 --- /dev/null +++ b/tests/html-tests/tests/DeprecatedFunction2.html.ref @@ -0,0 +1,83 @@ +<!DOCTYPE html PUBLIC "-//W3C//DTD XHTML 1.0 Transitional//EN" "http://www.w3.org/TR/xhtml1/DTD/xhtml1-transitional.dtd"> +<html xmlns="http://www.w3.org/1999/xhtml" +><head + ><meta http-equiv="Content-Type" content="text/html; charset=UTF-8" + /><title + >DeprecatedFunction2</title + ><link href="ocean.css" rel="stylesheet" type="text/css" title="Ocean" + /><script src="haddock-util.js" type="text/javascript" + ></script + ><script type="text/javascript" + >//<![CDATA[ +window.onload = function () {pageLoad();setSynopsis("mini_DeprecatedFunction2.html");}; +//]]> +</script + ></head + ><body + ><div id="package-header" + ><ul class="links" id="page-menu" + ><li + ><a href="" + >Contents</a + ></li + ><li + ><a href="" + >Index</a + ></li + ></ul + ><p class="caption" class="empty" + > </p + ></div + ><div id="content" + ><div id="module-header" + ><table class="info" + ><tr + ><th + >Safe Haskell</th + ><td + >None</td + ></tr + ></table + ><p class="caption" + >DeprecatedFunction2</p + ></div + ><div id="synopsis" + ><p id="control.syn" class="caption expander" onclick="toggleSection('syn')" + >Synopsis</p + ><ul id="section.syn" class="hide" onclick="toggleSection('syn')" + ><li class="src short" + ><a href="" + >foo</a + > :: <a href="" + >Int</a + ></li + ></ul + ></div + ><div id="interface" + ><h1 + >Documentation</h1 + ><div class="top" + ><p class="src" + ><a name="v:foo" class="def" + >foo</a + > :: <a href="" + >Int</a + ></p + ><div class="doc" + ><div class="warning" + ><p + >Deprecated: use bar instead</p + ></div + ></div + ></div + ></div + ></div + ><div id="footer" + ><p + >Produced by <a href="" + >Haddock</a + > version 2.10.0</p + ></div + ></body + ></html +> diff --git a/tests/html-tests/tests/DeprecatedFunction3.hs b/tests/html-tests/tests/DeprecatedFunction3.hs new file mode 100644 index 00000000..ca719bda --- /dev/null +++ b/tests/html-tests/tests/DeprecatedFunction3.hs @@ -0,0 +1,6 @@ +module DeprecatedFunction3 where + + + +foo = 23 +{-# DEPRECATED foo "use bar instead" #-} diff --git a/tests/html-tests/tests/DeprecatedFunction3.html.ref b/tests/html-tests/tests/DeprecatedFunction3.html.ref new file mode 100644 index 00000000..246c3c69 --- /dev/null +++ b/tests/html-tests/tests/DeprecatedFunction3.html.ref @@ -0,0 +1,83 @@ +<!DOCTYPE html PUBLIC "-//W3C//DTD XHTML 1.0 Transitional//EN" "http://www.w3.org/TR/xhtml1/DTD/xhtml1-transitional.dtd"> +<html xmlns="http://www.w3.org/1999/xhtml" +><head + ><meta http-equiv="Content-Type" content="text/html; charset=UTF-8" + /><title + >DeprecatedFunction3</title + ><link href="ocean.css" rel="stylesheet" type="text/css" title="Ocean" + /><script src="haddock-util.js" type="text/javascript" + ></script + ><script type="text/javascript" + >//<![CDATA[ +window.onload = function () {pageLoad();setSynopsis("mini_DeprecatedFunction3.html");}; +//]]> +</script + ></head + ><body + ><div id="package-header" + ><ul class="links" id="page-menu" + ><li + ><a href="" + >Contents</a + ></li + ><li + ><a href="" + >Index</a + ></li + ></ul + ><p class="caption" class="empty" + > </p + ></div + ><div id="content" + ><div id="module-header" + ><table class="info" + ><tr + ><th + >Safe Haskell</th + ><td + >None</td + ></tr + ></table + ><p class="caption" + >DeprecatedFunction3</p + ></div + ><div id="synopsis" + ><p id="control.syn" class="caption expander" onclick="toggleSection('syn')" + >Synopsis</p + ><ul id="section.syn" class="hide" onclick="toggleSection('syn')" + ><li class="src short" + ><a href="" + >foo</a + > :: <a href="" + >Integer</a + ></li + ></ul + ></div + ><div id="interface" + ><h1 + >Documentation</h1 + ><div class="top" + ><p class="src" + ><a name="v:foo" class="def" + >foo</a + > :: <a href="" + >Integer</a + ></p + ><div class="doc" + ><div class="warning" + ><p + >Deprecated: use bar instead</p + ></div + ></div + ></div + ></div + ></div + ><div id="footer" + ><p + >Produced by <a href="" + >Haddock</a + > version 2.10.0</p + ></div + ></body + ></html +> diff --git a/tests/html-tests/tests/DeprecatedModule.hs b/tests/html-tests/tests/DeprecatedModule.hs new file mode 100644 index 00000000..61a09d64 --- /dev/null +++ b/tests/html-tests/tests/DeprecatedModule.hs @@ -0,0 +1,5 @@ +-- | Documentation for "DeprecatedModule". +module DeprecatedModule {-# DEPRECATED "Use Foo instead" #-} where + +foo :: Int +foo = 23 diff --git a/tests/html-tests/tests/DeprecatedModule.html.ref b/tests/html-tests/tests/DeprecatedModule.html.ref new file mode 100644 index 00000000..6f79f47c --- /dev/null +++ b/tests/html-tests/tests/DeprecatedModule.html.ref @@ -0,0 +1,80 @@ +<!DOCTYPE html PUBLIC "-//W3C//DTD XHTML 1.0 Transitional//EN" "http://www.w3.org/TR/xhtml1/DTD/xhtml1-transitional.dtd"> +<html xmlns="http://www.w3.org/1999/xhtml" +><head + ><meta http-equiv="Content-Type" content="text/html; charset=UTF-8" + /><title + >DeprecatedModule</title + ><link href="ocean.css" rel="stylesheet" type="text/css" title="Ocean" + /><script src="haddock-util.js" type="text/javascript" + ></script + ><script type="text/javascript" + >//<![CDATA[ +window.onload = function () {pageLoad();setSynopsis("mini_DeprecatedModule.html");}; +//]]> +</script + ></head + ><body + ><div id="package-header" + ><ul class="links" id="page-menu" + ><li + ><a href="" + >Contents</a + ></li + ><li + ><a href="" + >Index</a + ></li + ></ul + ><p class="caption" class="empty" + > </p + ></div + ><div id="content" + ><div id="module-header" + ><table class="info" + ><tr + ><th + >Safe Haskell</th + ><td + >None</td + ></tr + ></table + ><p class="caption" + >DeprecatedModule</p + ></div + ><div id="description" + ><p class="caption" + >Description</p + ><div class="doc" + ><div class="warning" + ><p + >Deprecated: Use Foo instead</p + ></div + ><p + >Documentation for <a href="" + >DeprecatedModule</a + >. +</p + ></div + ></div + ><div id="interface" + ><h1 + >Documentation</h1 + ><div class="top" + ><p class="src" + ><a name="v:foo" class="def" + >foo</a + > :: <a href="" + >Int</a + ></p + ></div + ></div + ></div + ><div id="footer" + ><p + >Produced by <a href="" + >Haddock</a + > version 2.10.0</p + ></div + ></body + ></html +> diff --git a/tests/html-tests/tests/DeprecatedModule2.hs b/tests/html-tests/tests/DeprecatedModule2.hs new file mode 100644 index 00000000..94185297 --- /dev/null +++ b/tests/html-tests/tests/DeprecatedModule2.hs @@ -0,0 +1,4 @@ +module DeprecatedModule2 {-# DEPRECATED "Use Foo instead" #-} where + +foo :: Int +foo = 23 diff --git a/tests/html-tests/tests/DeprecatedModule2.html.ref b/tests/html-tests/tests/DeprecatedModule2.html.ref new file mode 100644 index 00000000..3a62c842 --- /dev/null +++ b/tests/html-tests/tests/DeprecatedModule2.html.ref @@ -0,0 +1,75 @@ +<!DOCTYPE html PUBLIC "-//W3C//DTD XHTML 1.0 Transitional//EN" "http://www.w3.org/TR/xhtml1/DTD/xhtml1-transitional.dtd"> +<html xmlns="http://www.w3.org/1999/xhtml" +><head + ><meta http-equiv="Content-Type" content="text/html; charset=UTF-8" + /><title + >DeprecatedModule2</title + ><link href="ocean.css" rel="stylesheet" type="text/css" title="Ocean" + /><script src="haddock-util.js" type="text/javascript" + ></script + ><script type="text/javascript" + >//<![CDATA[ +window.onload = function () {pageLoad();setSynopsis("mini_DeprecatedModule2.html");}; +//]]> +</script + ></head + ><body + ><div id="package-header" + ><ul class="links" id="page-menu" + ><li + ><a href="" + >Contents</a + ></li + ><li + ><a href="" + >Index</a + ></li + ></ul + ><p class="caption" class="empty" + > </p + ></div + ><div id="content" + ><div id="module-header" + ><table class="info" + ><tr + ><th + >Safe Haskell</th + ><td + >None</td + ></tr + ></table + ><p class="caption" + >DeprecatedModule2</p + ></div + ><div id="description" + ><p class="caption" + >Description</p + ><div class="doc" + ><div class="warning" + ><p + >Deprecated: Use Foo instead</p + ></div + ></div + ></div + ><div id="interface" + ><h1 + >Documentation</h1 + ><div class="top" + ><p class="src" + ><a name="v:foo" class="def" + >foo</a + > :: <a href="" + >Int</a + ></p + ></div + ></div + ></div + ><div id="footer" + ><p + >Produced by <a href="" + >Haddock</a + > version 2.10.0</p + ></div + ></body + ></html +> diff --git a/tests/html-tests/tests/DeprecatedNewtype.hs b/tests/html-tests/tests/DeprecatedNewtype.hs new file mode 100644 index 00000000..254f1f55 --- /dev/null +++ b/tests/html-tests/tests/DeprecatedNewtype.hs @@ -0,0 +1,10 @@ +module DeprecatedNewtype where + +-- | some documentation +newtype SomeNewType = SomeNewTypeConst String {- ^ constructor docu -} +{-# DEPRECATED SomeNewType "SomeNewType" #-} +{-# DEPRECATED SomeNewTypeConst "SomeNewTypeConst" #-} + +newtype SomeOtherNewType = SomeOtherNewTypeConst String +{-# DEPRECATED SomeOtherNewType "SomeOtherNewType" #-} +{-# DEPRECATED SomeOtherNewTypeConst "SomeOtherNewTypeConst" #-} diff --git a/tests/html-tests/tests/DeprecatedNewtype.html.ref b/tests/html-tests/tests/DeprecatedNewtype.html.ref new file mode 100644 index 00000000..ce19efa2 --- /dev/null +++ b/tests/html-tests/tests/DeprecatedNewtype.html.ref @@ -0,0 +1,157 @@ +<!DOCTYPE html PUBLIC "-//W3C//DTD XHTML 1.0 Transitional//EN" "http://www.w3.org/TR/xhtml1/DTD/xhtml1-transitional.dtd"> +<html xmlns="http://www.w3.org/1999/xhtml" +><head + ><meta http-equiv="Content-Type" content="text/html; charset=UTF-8" + /><title + >DeprecatedNewtype</title + ><link href="ocean.css" rel="stylesheet" type="text/css" title="Ocean" + /><script src="haddock-util.js" type="text/javascript" + ></script + ><script type="text/javascript" + >//<![CDATA[ +window.onload = function () {pageLoad();setSynopsis("mini_DeprecatedNewtype.html");}; +//]]> +</script + ></head + ><body + ><div id="package-header" + ><ul class="links" id="page-menu" + ><li + ><a href="" + >Contents</a + ></li + ><li + ><a href="" + >Index</a + ></li + ></ul + ><p class="caption" class="empty" + > </p + ></div + ><div id="content" + ><div id="module-header" + ><table class="info" + ><tr + ><th + >Safe Haskell</th + ><td + >None</td + ></tr + ></table + ><p class="caption" + >DeprecatedNewtype</p + ></div + ><div id="synopsis" + ><p id="control.syn" class="caption expander" onclick="toggleSection('syn')" + >Synopsis</p + ><ul id="section.syn" class="hide" onclick="toggleSection('syn')" + ><li class="src short" + ><span class="keyword" + >newtype</span + > <a href="" + >SomeNewType</a + > = <a href="" + >SomeNewTypeConst</a + > <a href="" + >String</a + ></li + ><li class="src short" + ><span class="keyword" + >newtype</span + > <a href="" + >SomeOtherNewType</a + > = <a href="" + >SomeOtherNewTypeConst</a + > <a href="" + >String</a + ></li + ></ul + ></div + ><div id="interface" + ><h1 + >Documentation</h1 + ><div class="top" + ><p class="src" + ><span class="keyword" + >newtype</span + > <a name="t:SomeNewType" class="def" + >SomeNewType</a + > </p + ><div class="doc" + ><div class="warning" + ><p + >Deprecated: SomeNewType</p + ></div + ><p + >some documentation +</p + ></div + ><div class="subs constructors" + ><p class="caption" + >Constructors</p + ><table + ><tr + ><td class="src" + ><a name="v:SomeNewTypeConst" class="def" + >SomeNewTypeConst</a + > <a href="" + >String</a + ></td + ><td class="doc" + ><div class="warning" + ><p + >Deprecated: SomeNewTypeConst</p + ></div + ><p + >constructor docu +</p + ></td + ></tr + ></table + ></div + ></div + ><div class="top" + ><p class="src" + ><span class="keyword" + >newtype</span + > <a name="t:SomeOtherNewType" class="def" + >SomeOtherNewType</a + > </p + ><div class="doc" + ><div class="warning" + ><p + >Deprecated: SomeOtherNewType</p + ></div + ></div + ><div class="subs constructors" + ><p class="caption" + >Constructors</p + ><table + ><tr + ><td class="src" + ><a name="v:SomeOtherNewTypeConst" class="def" + >SomeOtherNewTypeConst</a + > <a href="" + >String</a + ></td + ><td class="doc" + ><div class="warning" + ><p + >Deprecated: SomeOtherNewTypeConst</p + ></div + ></td + ></tr + ></table + ></div + ></div + ></div + ></div + ><div id="footer" + ><p + >Produced by <a href="" + >Haddock</a + > version 2.10.0</p + ></div + ></body + ></html +> diff --git a/tests/html-tests/tests/DeprecatedTypeFamily.hs b/tests/html-tests/tests/DeprecatedTypeFamily.hs new file mode 100644 index 00000000..70473bb8 --- /dev/null +++ b/tests/html-tests/tests/DeprecatedTypeFamily.hs @@ -0,0 +1,9 @@ +{-# LANGUAGE TypeFamilies #-} +module DeprecatedTypeFamily where + +-- | some documentation +data family SomeTypeFamily k :: * -> * +{-# DEPRECATED SomeTypeFamily "SomeTypeFamily" #-} + +data family SomeOtherTypeFamily k :: * -> * +{-# DEPRECATED SomeOtherTypeFamily "SomeOtherTypeFamily" #-} diff --git a/tests/html-tests/tests/DeprecatedTypeFamily.html.ref b/tests/html-tests/tests/DeprecatedTypeFamily.html.ref new file mode 100644 index 00000000..182f2c9e --- /dev/null +++ b/tests/html-tests/tests/DeprecatedTypeFamily.html.ref @@ -0,0 +1,106 @@ +<!DOCTYPE html PUBLIC "-//W3C//DTD XHTML 1.0 Transitional//EN" "http://www.w3.org/TR/xhtml1/DTD/xhtml1-transitional.dtd"> +<html xmlns="http://www.w3.org/1999/xhtml" +><head + ><meta http-equiv="Content-Type" content="text/html; charset=UTF-8" + /><title + >DeprecatedTypeFamily</title + ><link href="ocean.css" rel="stylesheet" type="text/css" title="Ocean" + /><script src="haddock-util.js" type="text/javascript" + ></script + ><script type="text/javascript" + >//<![CDATA[ +window.onload = function () {pageLoad();setSynopsis("mini_DeprecatedTypeFamily.html");}; +//]]> +</script + ></head + ><body + ><div id="package-header" + ><ul class="links" id="page-menu" + ><li + ><a href="" + >Contents</a + ></li + ><li + ><a href="" + >Index</a + ></li + ></ul + ><p class="caption" class="empty" + > </p + ></div + ><div id="content" + ><div id="module-header" + ><table class="info" + ><tr + ><th + >Safe Haskell</th + ><td + >None</td + ></tr + ></table + ><p class="caption" + >DeprecatedTypeFamily</p + ></div + ><div id="synopsis" + ><p id="control.syn" class="caption expander" onclick="toggleSection('syn')" + >Synopsis</p + ><ul id="section.syn" class="hide" onclick="toggleSection('syn')" + ><li class="src short" + ><span class="keyword" + >data family</span + > <a href="" + >SomeTypeFamily</a + > k :: * -> *</li + ><li class="src short" + ><span class="keyword" + >data family</span + > <a href="" + >SomeOtherTypeFamily</a + > k :: * -> *</li + ></ul + ></div + ><div id="interface" + ><h1 + >Documentation</h1 + ><div class="top" + ><p class="src" + ><span class="keyword" + >data family</span + > <a name="t:SomeTypeFamily" class="def" + >SomeTypeFamily</a + > k :: * -> *</p + ><div class="doc" + ><div class="warning" + ><p + >Deprecated: SomeTypeFamily</p + ></div + ><p + >some documentation +</p + ></div + ></div + ><div class="top" + ><p class="src" + ><span class="keyword" + >data family</span + > <a name="t:SomeOtherTypeFamily" class="def" + >SomeOtherTypeFamily</a + > k :: * -> *</p + ><div class="doc" + ><div class="warning" + ><p + >Deprecated: SomeOtherTypeFamily</p + ></div + ></div + ></div + ></div + ></div + ><div id="footer" + ><p + >Produced by <a href="" + >Haddock</a + > version 2.10.0</p + ></div + ></body + ></html +> diff --git a/tests/html-tests/tests/DeprecatedTypeSynonym.hs b/tests/html-tests/tests/DeprecatedTypeSynonym.hs new file mode 100644 index 00000000..34df47da --- /dev/null +++ b/tests/html-tests/tests/DeprecatedTypeSynonym.hs @@ -0,0 +1,9 @@ + +module DeprecatedTypeSynonym where + +-- | some documentation +type TypeSyn = String +{-# DEPRECATED TypeSyn "TypeSyn" #-} + +type OtherTypeSyn = String +{-# DEPRECATED OtherTypeSyn "OtherTypeSyn" #-} diff --git a/tests/html-tests/tests/DeprecatedTypeSynonym.html.ref b/tests/html-tests/tests/DeprecatedTypeSynonym.html.ref new file mode 100644 index 00000000..a063d8ce --- /dev/null +++ b/tests/html-tests/tests/DeprecatedTypeSynonym.html.ref @@ -0,0 +1,114 @@ +<!DOCTYPE html PUBLIC "-//W3C//DTD XHTML 1.0 Transitional//EN" "http://www.w3.org/TR/xhtml1/DTD/xhtml1-transitional.dtd"> +<html xmlns="http://www.w3.org/1999/xhtml" +><head + ><meta http-equiv="Content-Type" content="text/html; charset=UTF-8" + /><title + >DeprecatedTypeSynonym</title + ><link href="ocean.css" rel="stylesheet" type="text/css" title="Ocean" + /><script src="haddock-util.js" type="text/javascript" + ></script + ><script type="text/javascript" + >//<![CDATA[ +window.onload = function () {pageLoad();setSynopsis("mini_DeprecatedTypeSynonym.html");}; +//]]> +</script + ></head + ><body + ><div id="package-header" + ><ul class="links" id="page-menu" + ><li + ><a href="" + >Contents</a + ></li + ><li + ><a href="" + >Index</a + ></li + ></ul + ><p class="caption" class="empty" + > </p + ></div + ><div id="content" + ><div id="module-header" + ><table class="info" + ><tr + ><th + >Safe Haskell</th + ><td + >None</td + ></tr + ></table + ><p class="caption" + >DeprecatedTypeSynonym</p + ></div + ><div id="synopsis" + ><p id="control.syn" class="caption expander" onclick="toggleSection('syn')" + >Synopsis</p + ><ul id="section.syn" class="hide" onclick="toggleSection('syn')" + ><li class="src short" + ><span class="keyword" + >type</span + > <a href="" + >TypeSyn</a + > = <a href="" + >String</a + ></li + ><li class="src short" + ><span class="keyword" + >type</span + > <a href="" + >OtherTypeSyn</a + > = <a href="" + >String</a + ></li + ></ul + ></div + ><div id="interface" + ><h1 + >Documentation</h1 + ><div class="top" + ><p class="src" + ><span class="keyword" + >type</span + > <a name="t:TypeSyn" class="def" + >TypeSyn</a + > = <a href="" + >String</a + ></p + ><div class="doc" + ><div class="warning" + ><p + >Deprecated: TypeSyn</p + ></div + ><p + >some documentation +</p + ></div + ></div + ><div class="top" + ><p class="src" + ><span class="keyword" + >type</span + > <a name="t:OtherTypeSyn" class="def" + >OtherTypeSyn</a + > = <a href="" + >String</a + ></p + ><div class="doc" + ><div class="warning" + ><p + >Deprecated: OtherTypeSyn</p + ></div + ></div + ></div + ></div + ></div + ><div id="footer" + ><p + >Produced by <a href="" + >Haddock</a + > version 2.10.0</p + ></div + ></body + ></html +> diff --git a/tests/html-tests/tests/ModuleWithWarning.hs b/tests/html-tests/tests/ModuleWithWarning.hs new file mode 100644 index 00000000..2114bac6 --- /dev/null +++ b/tests/html-tests/tests/ModuleWithWarning.hs @@ -0,0 +1,5 @@ +-- | Documentation for "ModuleWithWarning". +module ModuleWithWarning {-# WARNING "This is an unstable interface." #-} where + +foo :: Int +foo = 23 diff --git a/tests/html-tests/tests/ModuleWithWarning.html.ref b/tests/html-tests/tests/ModuleWithWarning.html.ref new file mode 100644 index 00000000..a0df1418 --- /dev/null +++ b/tests/html-tests/tests/ModuleWithWarning.html.ref @@ -0,0 +1,80 @@ +<!DOCTYPE html PUBLIC "-//W3C//DTD XHTML 1.0 Transitional//EN" "http://www.w3.org/TR/xhtml1/DTD/xhtml1-transitional.dtd"> +<html xmlns="http://www.w3.org/1999/xhtml" +><head + ><meta http-equiv="Content-Type" content="text/html; charset=UTF-8" + /><title + >ModuleWithWarning</title + ><link href="ocean.css" rel="stylesheet" type="text/css" title="Ocean" + /><script src="haddock-util.js" type="text/javascript" + ></script + ><script type="text/javascript" + >//<![CDATA[ +window.onload = function () {pageLoad();setSynopsis("mini_ModuleWithWarning.html");}; +//]]> +</script + ></head + ><body + ><div id="package-header" + ><ul class="links" id="page-menu" + ><li + ><a href="" + >Contents</a + ></li + ><li + ><a href="" + >Index</a + ></li + ></ul + ><p class="caption" class="empty" + > </p + ></div + ><div id="content" + ><div id="module-header" + ><table class="info" + ><tr + ><th + >Safe Haskell</th + ><td + >None</td + ></tr + ></table + ><p class="caption" + >ModuleWithWarning</p + ></div + ><div id="description" + ><p class="caption" + >Description</p + ><div class="doc" + ><div class="warning" + ><p + >Warning: This is an unstable interface.</p + ></div + ><p + >Documentation for <a href="" + >ModuleWithWarning</a + >. +</p + ></div + ></div + ><div id="interface" + ><h1 + >Documentation</h1 + ><div class="top" + ><p class="src" + ><a name="v:foo" class="def" + >foo</a + > :: <a href="" + >Int</a + ></p + ></div + ></div + ></div + ><div id="footer" + ><p + >Produced by <a href="" + >Haddock</a + > version 2.10.0</p + ></div + ></body + ></html +> diff --git a/tests/html-tests/tests/frames.html.ref b/tests/html-tests/tests/frames.html.ref new file mode 100644 index 00000000..30ce1fa5 --- /dev/null +++ b/tests/html-tests/tests/frames.html.ref @@ -0,0 +1,28 @@ +<!DOCTYPE html + PUBLIC "-//W3C//DTD XHTML 1.0 Frameset//EN" + "http://www.w3.org/TR/xhtml1/DTD/xhtml1-frameset.dtd"> +<html xmlns="http://www.w3.org/1999/xhtml"> +<head> +<script src="haddock-util.js" type="text/javascript"></script> +<script type="text/javascript"><!-- +/* + + The synopsis frame needs to be updated using javascript, so we hide + it by default and only show it if javascript is enabled. + + TODO: provide some means to disable it. +*/ +function load() { + var d = document.getElementById("inner-fs"); + d.rows = "50%,50%"; + postReframe(); +} +--></script> +<frameset id="outer-fs" cols="25%,75%" onload="load()"> + <frameset id="inner-fs" rows="100%,0%"> + <frame src="index-frames.html" name="modules"> + <frame src="" name="synopsis"> + </frameset> + <frame src="index.html" name="main"> +</frameset> +</html> diff --git a/tests/html-tests/tests/mini_A.html.ref b/tests/html-tests/tests/mini_A.html.ref new file mode 100644 index 00000000..3de17437 --- /dev/null +++ b/tests/html-tests/tests/mini_A.html.ref @@ -0,0 +1,45 @@ +<!DOCTYPE html PUBLIC "-//W3C//DTD XHTML 1.0 Transitional//EN" "http://www.w3.org/TR/xhtml1/DTD/xhtml1-transitional.dtd"> +<html xmlns="http://www.w3.org/1999/xhtml" +><head + ><meta http-equiv="Content-Type" content="text/html; charset=UTF-8" + /><title + >A</title + ><link href="ocean.css" rel="stylesheet" type="text/css" title="Ocean" + /><script src="haddock-util.js" type="text/javascript" + ></script + ><script type="text/javascript" + >//<![CDATA[ +window.onload = function () {pageLoad();}; +//]]> +</script + ></head + ><body id="mini" + ><div id="module-header" + ><p class="caption" + >A</p + ></div + ><div id="interface" + ><div class="top" + ><p class="src" + ><span class="keyword" + >data</span + > <a href="" target="main" + >A</a + > </p + ></div + ><div class="top" + ><p class="src" + ><a href="" target="main" + >other</a + ></p + ></div + ><div class="top" + ><p class="src" + ><a href="" target="main" + >test2</a + ></p + ></div + ></div + ></body + ></html +> diff --git a/tests/html-tests/tests/mini_B.html.ref b/tests/html-tests/tests/mini_B.html.ref new file mode 100644 index 00000000..c4d21778 --- /dev/null +++ b/tests/html-tests/tests/mini_B.html.ref @@ -0,0 +1,31 @@ +<!DOCTYPE html PUBLIC "-//W3C//DTD XHTML 1.0 Transitional//EN" "http://www.w3.org/TR/xhtml1/DTD/xhtml1-transitional.dtd"> +<html xmlns="http://www.w3.org/1999/xhtml" +><head + ><meta http-equiv="Content-Type" content="text/html; charset=UTF-8" + /><title + >B</title + ><link href="ocean.css" rel="stylesheet" type="text/css" title="Ocean" + /><script src="haddock-util.js" type="text/javascript" + ></script + ><script type="text/javascript" + >//<![CDATA[ +window.onload = function () {pageLoad();}; +//]]> +</script + ></head + ><body id="mini" + ><div id="module-header" + ><p class="caption" + >B</p + ></div + ><div id="interface" + ><div class="top" + ><p class="src" + ><a href="" target="main" + >test</a + ></p + ></div + ></div + ></body + ></html +> diff --git a/tests/html-tests/tests/mini_Bug1.html.ref b/tests/html-tests/tests/mini_Bug1.html.ref new file mode 100644 index 00000000..adf81c73 --- /dev/null +++ b/tests/html-tests/tests/mini_Bug1.html.ref @@ -0,0 +1,33 @@ +<!DOCTYPE html PUBLIC "-//W3C//DTD XHTML 1.0 Transitional//EN" "http://www.w3.org/TR/xhtml1/DTD/xhtml1-transitional.dtd"> +<html xmlns="http://www.w3.org/1999/xhtml" +><head + ><meta http-equiv="Content-Type" content="text/html; charset=UTF-8" + /><title + >Bug1</title + ><link href="ocean.css" rel="stylesheet" type="text/css" title="Ocean" + /><script src="haddock-util.js" type="text/javascript" + ></script + ><script type="text/javascript" + >//<![CDATA[ +window.onload = function () {pageLoad();}; +//]]> +</script + ></head + ><body id="mini" + ><div id="module-header" + ><p class="caption" + >Bug1</p + ></div + ><div id="interface" + ><div class="top" + ><p class="src" + ><span class="keyword" + >data</span + > <a href="" target="main" + >T</a + > </p + ></div + ></div + ></body + ></html +> diff --git a/tests/html-tests/tests/mini_Bug2.html.ref b/tests/html-tests/tests/mini_Bug2.html.ref new file mode 100644 index 00000000..b673e459 --- /dev/null +++ b/tests/html-tests/tests/mini_Bug2.html.ref @@ -0,0 +1,31 @@ +<!DOCTYPE html PUBLIC "-//W3C//DTD XHTML 1.0 Transitional//EN" "http://www.w3.org/TR/xhtml1/DTD/xhtml1-transitional.dtd"> +<html xmlns="http://www.w3.org/1999/xhtml" +><head + ><meta http-equiv="Content-Type" content="text/html; charset=UTF-8" + /><title + >Bug2</title + ><link href="ocean.css" rel="stylesheet" type="text/css" title="Ocean" + /><script src="haddock-util.js" type="text/javascript" + ></script + ><script type="text/javascript" + >//<![CDATA[ +window.onload = function () {pageLoad();}; +//]]> +</script + ></head + ><body id="mini" + ><div id="module-header" + ><p class="caption" + >Bug2</p + ></div + ><div id="interface" + ><div class="top" + ><p class="src" + ><a href="" target="main" + >x</a + ></p + ></div + ></div + ></body + ></html +> diff --git a/tests/html-tests/tests/mini_Bug3.html.ref b/tests/html-tests/tests/mini_Bug3.html.ref new file mode 100644 index 00000000..af4cc445 --- /dev/null +++ b/tests/html-tests/tests/mini_Bug3.html.ref @@ -0,0 +1,31 @@ +<!DOCTYPE html PUBLIC "-//W3C//DTD XHTML 1.0 Transitional//EN" "http://www.w3.org/TR/xhtml1/DTD/xhtml1-transitional.dtd"> +<html xmlns="http://www.w3.org/1999/xhtml" +><head + ><meta http-equiv="Content-Type" content="text/html; charset=UTF-8" + /><title + >Bug3</title + ><link href="ocean.css" rel="stylesheet" type="text/css" title="Ocean" + /><script src="haddock-util.js" type="text/javascript" + ></script + ><script type="text/javascript" + >//<![CDATA[ +window.onload = function () {pageLoad();}; +//]]> +</script + ></head + ><body id="mini" + ><div id="module-header" + ><p class="caption" + >Bug3</p + ></div + ><div id="interface" + ><div class="top" + ><p class="src" + ><a href="" target="main" + >foo</a + ></p + ></div + ></div + ></body + ></html +> diff --git a/tests/html-tests/tests/mini_Bug4.html.ref b/tests/html-tests/tests/mini_Bug4.html.ref new file mode 100644 index 00000000..b403e94a --- /dev/null +++ b/tests/html-tests/tests/mini_Bug4.html.ref @@ -0,0 +1,31 @@ +<!DOCTYPE html PUBLIC "-//W3C//DTD XHTML 1.0 Transitional//EN" "http://www.w3.org/TR/xhtml1/DTD/xhtml1-transitional.dtd"> +<html xmlns="http://www.w3.org/1999/xhtml" +><head + ><meta http-equiv="Content-Type" content="text/html; charset=UTF-8" + /><title + >Bug4</title + ><link href="ocean.css" rel="stylesheet" type="text/css" title="Ocean" + /><script src="haddock-util.js" type="text/javascript" + ></script + ><script type="text/javascript" + >//<![CDATA[ +window.onload = function () {pageLoad();}; +//]]> +</script + ></head + ><body id="mini" + ><div id="module-header" + ><p class="caption" + >Bug4</p + ></div + ><div id="interface" + ><div class="top" + ><p class="src" + ><a href="" target="main" + >foo</a + ></p + ></div + ></div + ></body + ></html +> diff --git a/tests/html-tests/tests/mini_Bug6.html.ref b/tests/html-tests/tests/mini_Bug6.html.ref new file mode 100644 index 00000000..5c5c1119 --- /dev/null +++ b/tests/html-tests/tests/mini_Bug6.html.ref @@ -0,0 +1,65 @@ +<!DOCTYPE html PUBLIC "-//W3C//DTD XHTML 1.0 Transitional//EN" "http://www.w3.org/TR/xhtml1/DTD/xhtml1-transitional.dtd"> +<html xmlns="http://www.w3.org/1999/xhtml" +><head + ><meta http-equiv="Content-Type" content="text/html; charset=UTF-8" + /><title + >Bug6</title + ><link href="ocean.css" rel="stylesheet" type="text/css" title="Ocean" + /><script src="haddock-util.js" type="text/javascript" + ></script + ><script type="text/javascript" + >//<![CDATA[ +window.onload = function () {pageLoad();}; +//]]> +</script + ></head + ><body id="mini" + ><div id="module-header" + ><p class="caption" + >Bug6</p + ></div + ><div id="interface" + ><div class="top" + ><p class="src" + ><span class="keyword" + >data</span + > <a href="" target="main" + >A</a + > </p + ></div + ><div class="top" + ><p class="src" + ><span class="keyword" + >data</span + > <a href="" target="main" + >B</a + > </p + ></div + ><div class="top" + ><p class="src" + ><span class="keyword" + >data</span + > <a href="" target="main" + >C</a + > </p + ></div + ><div class="top" + ><p class="src" + ><span class="keyword" + >data</span + > <a href="" target="main" + >D</a + > </p + ></div + ><div class="top" + ><p class="src" + ><span class="keyword" + >data</span + > <a href="" target="main" + >E</a + > </p + ></div + ></div + ></body + ></html +> diff --git a/tests/html-tests/tests/mini_Bug7.html.ref b/tests/html-tests/tests/mini_Bug7.html.ref new file mode 100644 index 00000000..1bec82ee --- /dev/null +++ b/tests/html-tests/tests/mini_Bug7.html.ref @@ -0,0 +1,41 @@ +<!DOCTYPE html PUBLIC "-//W3C//DTD XHTML 1.0 Transitional//EN" "http://www.w3.org/TR/xhtml1/DTD/xhtml1-transitional.dtd"> +<html xmlns="http://www.w3.org/1999/xhtml" +><head + ><meta http-equiv="Content-Type" content="text/html; charset=UTF-8" + /><title + >Bug7</title + ><link href="ocean.css" rel="stylesheet" type="text/css" title="Ocean" + /><script src="haddock-util.js" type="text/javascript" + ></script + ><script type="text/javascript" + >//<![CDATA[ +window.onload = function () {pageLoad();}; +//]]> +</script + ></head + ><body id="mini" + ><div id="module-header" + ><p class="caption" + >Bug7</p + ></div + ><div id="interface" + ><div class="top" + ><p class="src" + ><span class="keyword" + >data</span + > <a href="" target="main" + >Foo</a + > </p + ></div + ><div class="top" + ><p class="src" + ><span class="keyword" + >class</span + > <a href="" target="main" + >Bar</a + > x y</p + ></div + ></div + ></body + ></html +> diff --git a/tests/html-tests/tests/mini_Bug8.html.ref b/tests/html-tests/tests/mini_Bug8.html.ref new file mode 100644 index 00000000..070dbcf8 --- /dev/null +++ b/tests/html-tests/tests/mini_Bug8.html.ref @@ -0,0 +1,63 @@ +<!DOCTYPE html PUBLIC "-//W3C//DTD XHTML 1.0 Transitional//EN" "http://www.w3.org/TR/xhtml1/DTD/xhtml1-transitional.dtd"> +<html xmlns="http://www.w3.org/1999/xhtml" +><head + ><meta http-equiv="Content-Type" content="text/html; charset=UTF-8" + /><title + >Bug8</title + ><link href="ocean.css" rel="stylesheet" type="text/css" title="Ocean" + /><script src="haddock-util.js" type="text/javascript" + ></script + ><script type="text/javascript" + >//<![CDATA[ +window.onload = function () {pageLoad();}; +//]]> +</script + ></head + ><body id="mini" + ><div id="module-header" + ><p class="caption" + >Bug8</p + ></div + ><div id="interface" + ><div class="top" + ><p class="src" + ><span class="keyword" + >data</span + > <a href="" target="main" + >Typ</a + > </p + ></div + ><div class="top" + ><p class="src" + ><a href="" target="main" + >(-->)</a + ></p + ></div + ><div class="top" + ><p class="src" + ><a href="" target="main" + >(--->)</a + ></p + ></div + ><div class="top" + ><p class="src" + ><a href="" target="main" + >s</a + ></p + ></div + ><div class="top" + ><p class="src" + ><a href="" target="main" + >t</a + ></p + ></div + ><div class="top" + ><p class="src" + ><a href="" target="main" + >main</a + ></p + ></div + ></div + ></body + ></html +> diff --git a/tests/html-tests/tests/mini_BugDeprecated.html.ref b/tests/html-tests/tests/mini_BugDeprecated.html.ref new file mode 100644 index 00000000..f0410137 --- /dev/null +++ b/tests/html-tests/tests/mini_BugDeprecated.html.ref @@ -0,0 +1,61 @@ +<!DOCTYPE html PUBLIC "-//W3C//DTD XHTML 1.0 Transitional//EN" "http://www.w3.org/TR/xhtml1/DTD/xhtml1-transitional.dtd"> +<html xmlns="http://www.w3.org/1999/xhtml" +><head + ><meta http-equiv="Content-Type" content="text/html; charset=UTF-8" + /><title + >BugDeprecated</title + ><link href="ocean.css" rel="stylesheet" type="text/css" title="Ocean" + /><script src="haddock-util.js" type="text/javascript" + ></script + ><script type="text/javascript" + >//<![CDATA[ +window.onload = function () {pageLoad();}; +//]]> +</script + ></head + ><body id="mini" + ><div id="module-header" + ><p class="caption" + >BugDeprecated</p + ></div + ><div id="interface" + ><div class="top" + ><p class="src" + ><a href="" target="main" + >foo</a + ></p + ></div + ><div class="top" + ><p class="src" + ><a href="" target="main" + >baz</a + ></p + ></div + ><div class="top" + ><p class="src" + ><a href="" target="main" + >bar</a + ></p + ></div + ><div class="top" + ><p class="src" + ><a href="" target="main" + >one</a + ></p + ></div + ><div class="top" + ><p class="src" + ><a href="" target="main" + >three</a + ></p + ></div + ><div class="top" + ><p class="src" + ><a href="" target="main" + >two</a + ></p + ></div + ></div + ></body + ></html +> diff --git a/tests/html-tests/tests/mini_BugExportHeadings.html.ref b/tests/html-tests/tests/mini_BugExportHeadings.html.ref new file mode 100644 index 00000000..b481720d --- /dev/null +++ b/tests/html-tests/tests/mini_BugExportHeadings.html.ref @@ -0,0 +1,79 @@ +<!DOCTYPE html PUBLIC "-//W3C//DTD XHTML 1.0 Transitional//EN" "http://www.w3.org/TR/xhtml1/DTD/xhtml1-transitional.dtd"> +<html xmlns="http://www.w3.org/1999/xhtml" +><head + ><meta http-equiv="Content-Type" content="text/html; charset=UTF-8" + /><title + >BugExportHeadings</title + ><link href="ocean.css" rel="stylesheet" type="text/css" title="Ocean" + /><script src="haddock-util.js" type="text/javascript" + ></script + ><script type="text/javascript" + >//<![CDATA[ +window.onload = function () {pageLoad();}; +//]]> +</script + ></head + ><body id="mini" + ><div id="module-header" + ><p class="caption" + >BugExportHeadings</p + ></div + ><div id="interface" + ><h1 + >Foo +</h1 + ><div class="top" + ><p class="src" + ><a href="" target="main" + >foo</a + ></p + ></div + ><h1 + >Bar +</h1 + ><div class="top" + ><p class="src" + ><a href="" target="main" + >bar</a + ></p + ></div + ><h1 + >Baz +</h1 + ><div class="top" + ><p class="src" + ><a href="" target="main" + >baz</a + ></p + ></div + ><h1 + >One +</h1 + ><div class="top" + ><p class="src" + ><a href="" target="main" + >one</a + ></p + ></div + ><h1 + >Two +</h1 + ><div class="top" + ><p class="src" + ><a href="" target="main" + >two</a + ></p + ></div + ><h1 + >Three +</h1 + ><div class="top" + ><p class="src" + ><a href="" target="main" + >three</a + ></p + ></div + ></div + ></body + ></html +> diff --git a/tests/html-tests/tests/mini_Bugs.html.ref b/tests/html-tests/tests/mini_Bugs.html.ref new file mode 100644 index 00000000..3c758375 --- /dev/null +++ b/tests/html-tests/tests/mini_Bugs.html.ref @@ -0,0 +1,33 @@ +<!DOCTYPE html PUBLIC "-//W3C//DTD XHTML 1.0 Transitional//EN" "http://www.w3.org/TR/xhtml1/DTD/xhtml1-transitional.dtd"> +<html xmlns="http://www.w3.org/1999/xhtml" +><head + ><meta http-equiv="Content-Type" content="text/html; charset=UTF-8" + /><title + >Bugs</title + ><link href="ocean.css" rel="stylesheet" type="text/css" title="Ocean" + /><script src="haddock-util.js" type="text/javascript" + ></script + ><script type="text/javascript" + >//<![CDATA[ +window.onload = function () {pageLoad();}; +//]]> +</script + ></head + ><body id="mini" + ><div id="module-header" + ><p class="caption" + >Bugs</p + ></div + ><div id="interface" + ><div class="top" + ><p class="src" + ><span class="keyword" + >data</span + > <a href="" target="main" + >A</a + > a</p + ></div + ></div + ></body + ></html +> diff --git a/tests/html-tests/tests/mini_CrossPackageDocs.html.ref b/tests/html-tests/tests/mini_CrossPackageDocs.html.ref new file mode 100644 index 00000000..9d957c1e --- /dev/null +++ b/tests/html-tests/tests/mini_CrossPackageDocs.html.ref @@ -0,0 +1,45 @@ +<!DOCTYPE html PUBLIC "-//W3C//DTD XHTML 1.0 Transitional//EN" "http://www.w3.org/TR/xhtml1/DTD/xhtml1-transitional.dtd"> +<html xmlns="http://www.w3.org/1999/xhtml" +><head + ><meta http-equiv="Content-Type" content="text/html; charset=UTF-8" + /><title + >CrossPackageDocs</title + ><link href="ocean.css" rel="stylesheet" type="text/css" title="Ocean" + /><script src="haddock-util.js" type="text/javascript" + ></script + ><script type="text/javascript" + >//<![CDATA[ +window.onload = function () {pageLoad();}; +//]]> +</script + ></head + ><body id="mini" + ><div id="module-header" + ><p class="caption" + >CrossPackageDocs</p + ></div + ><div id="interface" + ><div class="top" + ><p class="src" + ><a href="" target="main" + >map</a + ></p + ></div + ><div class="top" + ><p class="src" + ><span class="keyword" + >class</span + > <a href="" target="main" + >Monad</a + > m</p + ></div + ><div class="top" + ><p class="src" + ><a href="" target="main" + >runInteractiveProcess</a + ></p + ></div + ></div + ></body + ></html +> diff --git a/tests/html-tests/tests/mini_DeprecatedClass.html.ref b/tests/html-tests/tests/mini_DeprecatedClass.html.ref new file mode 100644 index 00000000..3923c1ff --- /dev/null +++ b/tests/html-tests/tests/mini_DeprecatedClass.html.ref @@ -0,0 +1,41 @@ +<!DOCTYPE html PUBLIC "-//W3C//DTD XHTML 1.0 Transitional//EN" "http://www.w3.org/TR/xhtml1/DTD/xhtml1-transitional.dtd"> +<html xmlns="http://www.w3.org/1999/xhtml" +><head + ><meta http-equiv="Content-Type" content="text/html; charset=UTF-8" + /><title + >DeprecatedClass</title + ><link href="ocean.css" rel="stylesheet" type="text/css" title="Ocean" + /><script src="haddock-util.js" type="text/javascript" + ></script + ><script type="text/javascript" + >//<![CDATA[ +window.onload = function () {pageLoad();}; +//]]> +</script + ></head + ><body id="mini" + ><div id="module-header" + ><p class="caption" + >DeprecatedClass</p + ></div + ><div id="interface" + ><div class="top" + ><p class="src" + ><span class="keyword" + >class</span + > <a href="" target="main" + >SomeClass</a + > a</p + ></div + ><div class="top" + ><p class="src" + ><span class="keyword" + >class</span + > <a href="" target="main" + >SomeOtherClass</a + > a</p + ></div + ></div + ></body + ></html +> diff --git a/tests/html-tests/tests/mini_DeprecatedData.html.ref b/tests/html-tests/tests/mini_DeprecatedData.html.ref new file mode 100644 index 00000000..8ef20113 --- /dev/null +++ b/tests/html-tests/tests/mini_DeprecatedData.html.ref @@ -0,0 +1,41 @@ +<!DOCTYPE html PUBLIC "-//W3C//DTD XHTML 1.0 Transitional//EN" "http://www.w3.org/TR/xhtml1/DTD/xhtml1-transitional.dtd"> +<html xmlns="http://www.w3.org/1999/xhtml" +><head + ><meta http-equiv="Content-Type" content="text/html; charset=UTF-8" + /><title + >DeprecatedData</title + ><link href="ocean.css" rel="stylesheet" type="text/css" title="Ocean" + /><script src="haddock-util.js" type="text/javascript" + ></script + ><script type="text/javascript" + >//<![CDATA[ +window.onload = function () {pageLoad();}; +//]]> +</script + ></head + ><body id="mini" + ><div id="module-header" + ><p class="caption" + >DeprecatedData</p + ></div + ><div id="interface" + ><div class="top" + ><p class="src" + ><span class="keyword" + >data</span + > <a href="" target="main" + >Foo</a + > </p + ></div + ><div class="top" + ><p class="src" + ><span class="keyword" + >data</span + > <a href="" target="main" + >One</a + > </p + ></div + ></div + ></body + ></html +> diff --git a/tests/html-tests/tests/mini_DeprecatedFunction.html.ref b/tests/html-tests/tests/mini_DeprecatedFunction.html.ref new file mode 100644 index 00000000..17d3e526 --- /dev/null +++ b/tests/html-tests/tests/mini_DeprecatedFunction.html.ref @@ -0,0 +1,31 @@ +<!DOCTYPE html PUBLIC "-//W3C//DTD XHTML 1.0 Transitional//EN" "http://www.w3.org/TR/xhtml1/DTD/xhtml1-transitional.dtd"> +<html xmlns="http://www.w3.org/1999/xhtml" +><head + ><meta http-equiv="Content-Type" content="text/html; charset=UTF-8" + /><title + >DeprecatedFunction</title + ><link href="ocean.css" rel="stylesheet" type="text/css" title="Ocean" + /><script src="haddock-util.js" type="text/javascript" + ></script + ><script type="text/javascript" + >//<![CDATA[ +window.onload = function () {pageLoad();}; +//]]> +</script + ></head + ><body id="mini" + ><div id="module-header" + ><p class="caption" + >DeprecatedFunction</p + ></div + ><div id="interface" + ><div class="top" + ><p class="src" + ><a href="" target="main" + >foo</a + ></p + ></div + ></div + ></body + ></html +> diff --git a/tests/html-tests/tests/mini_DeprecatedFunction2.html.ref b/tests/html-tests/tests/mini_DeprecatedFunction2.html.ref new file mode 100644 index 00000000..a03991a9 --- /dev/null +++ b/tests/html-tests/tests/mini_DeprecatedFunction2.html.ref @@ -0,0 +1,31 @@ +<!DOCTYPE html PUBLIC "-//W3C//DTD XHTML 1.0 Transitional//EN" "http://www.w3.org/TR/xhtml1/DTD/xhtml1-transitional.dtd"> +<html xmlns="http://www.w3.org/1999/xhtml" +><head + ><meta http-equiv="Content-Type" content="text/html; charset=UTF-8" + /><title + >DeprecatedFunction2</title + ><link href="ocean.css" rel="stylesheet" type="text/css" title="Ocean" + /><script src="haddock-util.js" type="text/javascript" + ></script + ><script type="text/javascript" + >//<![CDATA[ +window.onload = function () {pageLoad();}; +//]]> +</script + ></head + ><body id="mini" + ><div id="module-header" + ><p class="caption" + >DeprecatedFunction2</p + ></div + ><div id="interface" + ><div class="top" + ><p class="src" + ><a href="" target="main" + >foo</a + ></p + ></div + ></div + ></body + ></html +> diff --git a/tests/html-tests/tests/mini_DeprecatedFunction3.html.ref b/tests/html-tests/tests/mini_DeprecatedFunction3.html.ref new file mode 100644 index 00000000..4ea60339 --- /dev/null +++ b/tests/html-tests/tests/mini_DeprecatedFunction3.html.ref @@ -0,0 +1,31 @@ +<!DOCTYPE html PUBLIC "-//W3C//DTD XHTML 1.0 Transitional//EN" "http://www.w3.org/TR/xhtml1/DTD/xhtml1-transitional.dtd"> +<html xmlns="http://www.w3.org/1999/xhtml" +><head + ><meta http-equiv="Content-Type" content="text/html; charset=UTF-8" + /><title + >DeprecatedFunction3</title + ><link href="ocean.css" rel="stylesheet" type="text/css" title="Ocean" + /><script src="haddock-util.js" type="text/javascript" + ></script + ><script type="text/javascript" + >//<![CDATA[ +window.onload = function () {pageLoad();}; +//]]> +</script + ></head + ><body id="mini" + ><div id="module-header" + ><p class="caption" + >DeprecatedFunction3</p + ></div + ><div id="interface" + ><div class="top" + ><p class="src" + ><a href="" target="main" + >foo</a + ></p + ></div + ></div + ></body + ></html +> diff --git a/tests/html-tests/tests/mini_DeprecatedModule.html.ref b/tests/html-tests/tests/mini_DeprecatedModule.html.ref new file mode 100644 index 00000000..bfdef611 --- /dev/null +++ b/tests/html-tests/tests/mini_DeprecatedModule.html.ref @@ -0,0 +1,31 @@ +<!DOCTYPE html PUBLIC "-//W3C//DTD XHTML 1.0 Transitional//EN" "http://www.w3.org/TR/xhtml1/DTD/xhtml1-transitional.dtd"> +<html xmlns="http://www.w3.org/1999/xhtml" +><head + ><meta http-equiv="Content-Type" content="text/html; charset=UTF-8" + /><title + >DeprecatedModule</title + ><link href="ocean.css" rel="stylesheet" type="text/css" title="Ocean" + /><script src="haddock-util.js" type="text/javascript" + ></script + ><script type="text/javascript" + >//<![CDATA[ +window.onload = function () {pageLoad();}; +//]]> +</script + ></head + ><body id="mini" + ><div id="module-header" + ><p class="caption" + >DeprecatedModule</p + ></div + ><div id="interface" + ><div class="top" + ><p class="src" + ><a href="" target="main" + >foo</a + ></p + ></div + ></div + ></body + ></html +> diff --git a/tests/html-tests/tests/mini_DeprecatedModule2.html.ref b/tests/html-tests/tests/mini_DeprecatedModule2.html.ref new file mode 100644 index 00000000..dbcc43b9 --- /dev/null +++ b/tests/html-tests/tests/mini_DeprecatedModule2.html.ref @@ -0,0 +1,31 @@ +<!DOCTYPE html PUBLIC "-//W3C//DTD XHTML 1.0 Transitional//EN" "http://www.w3.org/TR/xhtml1/DTD/xhtml1-transitional.dtd"> +<html xmlns="http://www.w3.org/1999/xhtml" +><head + ><meta http-equiv="Content-Type" content="text/html; charset=UTF-8" + /><title + >DeprecatedModule2</title + ><link href="ocean.css" rel="stylesheet" type="text/css" title="Ocean" + /><script src="haddock-util.js" type="text/javascript" + ></script + ><script type="text/javascript" + >//<![CDATA[ +window.onload = function () {pageLoad();}; +//]]> +</script + ></head + ><body id="mini" + ><div id="module-header" + ><p class="caption" + >DeprecatedModule2</p + ></div + ><div id="interface" + ><div class="top" + ><p class="src" + ><a href="" target="main" + >foo</a + ></p + ></div + ></div + ></body + ></html +> diff --git a/tests/html-tests/tests/mini_DeprecatedNewtype.html.ref b/tests/html-tests/tests/mini_DeprecatedNewtype.html.ref new file mode 100644 index 00000000..a913525f --- /dev/null +++ b/tests/html-tests/tests/mini_DeprecatedNewtype.html.ref @@ -0,0 +1,41 @@ +<!DOCTYPE html PUBLIC "-//W3C//DTD XHTML 1.0 Transitional//EN" "http://www.w3.org/TR/xhtml1/DTD/xhtml1-transitional.dtd"> +<html xmlns="http://www.w3.org/1999/xhtml" +><head + ><meta http-equiv="Content-Type" content="text/html; charset=UTF-8" + /><title + >DeprecatedNewtype</title + ><link href="ocean.css" rel="stylesheet" type="text/css" title="Ocean" + /><script src="haddock-util.js" type="text/javascript" + ></script + ><script type="text/javascript" + >//<![CDATA[ +window.onload = function () {pageLoad();}; +//]]> +</script + ></head + ><body id="mini" + ><div id="module-header" + ><p class="caption" + >DeprecatedNewtype</p + ></div + ><div id="interface" + ><div class="top" + ><p class="src" + ><span class="keyword" + >data</span + > <a href="" target="main" + >SomeNewType</a + > </p + ></div + ><div class="top" + ><p class="src" + ><span class="keyword" + >data</span + > <a href="" target="main" + >SomeOtherNewType</a + > </p + ></div + ></div + ></body + ></html +> diff --git a/tests/html-tests/tests/mini_DeprecatedTypeFamily.html.ref b/tests/html-tests/tests/mini_DeprecatedTypeFamily.html.ref new file mode 100644 index 00000000..c87d9637 --- /dev/null +++ b/tests/html-tests/tests/mini_DeprecatedTypeFamily.html.ref @@ -0,0 +1,41 @@ +<!DOCTYPE html PUBLIC "-//W3C//DTD XHTML 1.0 Transitional//EN" "http://www.w3.org/TR/xhtml1/DTD/xhtml1-transitional.dtd"> +<html xmlns="http://www.w3.org/1999/xhtml" +><head + ><meta http-equiv="Content-Type" content="text/html; charset=UTF-8" + /><title + >DeprecatedTypeFamily</title + ><link href="ocean.css" rel="stylesheet" type="text/css" title="Ocean" + /><script src="haddock-util.js" type="text/javascript" + ></script + ><script type="text/javascript" + >//<![CDATA[ +window.onload = function () {pageLoad();}; +//]]> +</script + ></head + ><body id="mini" + ><div id="module-header" + ><p class="caption" + >DeprecatedTypeFamily</p + ></div + ><div id="interface" + ><div class="top" + ><p class="src" + ><span class="keyword" + >data family</span + > <a href="" + >SomeTypeFamily</a + > k :: * -> *</p + ></div + ><div class="top" + ><p class="src" + ><span class="keyword" + >data family</span + > <a href="" + >SomeOtherTypeFamily</a + > k :: * -> *</p + ></div + ></div + ></body + ></html +> diff --git a/tests/html-tests/tests/mini_DeprecatedTypeSynonym.html.ref b/tests/html-tests/tests/mini_DeprecatedTypeSynonym.html.ref new file mode 100644 index 00000000..5ade100d --- /dev/null +++ b/tests/html-tests/tests/mini_DeprecatedTypeSynonym.html.ref @@ -0,0 +1,41 @@ +<!DOCTYPE html PUBLIC "-//W3C//DTD XHTML 1.0 Transitional//EN" "http://www.w3.org/TR/xhtml1/DTD/xhtml1-transitional.dtd"> +<html xmlns="http://www.w3.org/1999/xhtml" +><head + ><meta http-equiv="Content-Type" content="text/html; charset=UTF-8" + /><title + >DeprecatedTypeSynonym</title + ><link href="ocean.css" rel="stylesheet" type="text/css" title="Ocean" + /><script src="haddock-util.js" type="text/javascript" + ></script + ><script type="text/javascript" + >//<![CDATA[ +window.onload = function () {pageLoad();}; +//]]> +</script + ></head + ><body id="mini" + ><div id="module-header" + ><p class="caption" + >DeprecatedTypeSynonym</p + ></div + ><div id="interface" + ><div class="top" + ><p class="src" + ><span class="keyword" + >type</span + > <a href="" target="main" + >TypeSyn</a + > </p + ></div + ><div class="top" + ><p class="src" + ><span class="keyword" + >type</span + > <a href="" target="main" + >OtherTypeSyn</a + > </p + ></div + ></div + ></body + ></html +> diff --git a/tests/html-tests/tests/mini_Examples.html.ref b/tests/html-tests/tests/mini_Examples.html.ref new file mode 100644 index 00000000..c99c2c48 --- /dev/null +++ b/tests/html-tests/tests/mini_Examples.html.ref @@ -0,0 +1,31 @@ +<!DOCTYPE html PUBLIC "-//W3C//DTD XHTML 1.0 Transitional//EN" "http://www.w3.org/TR/xhtml1/DTD/xhtml1-transitional.dtd"> +<html xmlns="http://www.w3.org/1999/xhtml" +><head + ><meta http-equiv="Content-Type" content="text/html; charset=UTF-8" + /><title + >Examples</title + ><link href="ocean.css" rel="stylesheet" type="text/css" title="Ocean" + /><script src="haddock-util.js" type="text/javascript" + ></script + ><script type="text/javascript" + >//<![CDATA[ +window.onload = function () {pageLoad();}; +//]]> +</script + ></head + ><body id="mini" + ><div id="module-header" + ><p class="caption" + >Examples</p + ></div + ><div id="interface" + ><div class="top" + ><p class="src" + ><a href="" target="main" + >fib</a + ></p + ></div + ></div + ></body + ></html +> diff --git a/tests/html-tests/tests/mini_FunArgs.html.ref b/tests/html-tests/tests/mini_FunArgs.html.ref new file mode 100644 index 00000000..89729720 --- /dev/null +++ b/tests/html-tests/tests/mini_FunArgs.html.ref @@ -0,0 +1,37 @@ +<!DOCTYPE html PUBLIC "-//W3C//DTD XHTML 1.0 Transitional//EN" "http://www.w3.org/TR/xhtml1/DTD/xhtml1-transitional.dtd"> +<html xmlns="http://www.w3.org/1999/xhtml" +><head + ><meta http-equiv="Content-Type" content="text/html; charset=UTF-8" + /><title + >FunArgs</title + ><link href="ocean.css" rel="stylesheet" type="text/css" title="Ocean" + /><script src="haddock-util.js" type="text/javascript" + ></script + ><script type="text/javascript" + >//<![CDATA[ +window.onload = function () {pageLoad();}; +//]]> +</script + ></head + ><body id="mini" + ><div id="module-header" + ><p class="caption" + >FunArgs</p + ></div + ><div id="interface" + ><div class="top" + ><p class="src" + ><a href="" target="main" + >f</a + ></p + ></div + ><div class="top" + ><p class="src" + ><a href="" target="main" + >g</a + ></p + ></div + ></div + ></body + ></html +> diff --git a/tests/html-tests/tests/mini_GADTRecords.html.ref b/tests/html-tests/tests/mini_GADTRecords.html.ref new file mode 100644 index 00000000..a8b838f0 --- /dev/null +++ b/tests/html-tests/tests/mini_GADTRecords.html.ref @@ -0,0 +1,33 @@ +<!DOCTYPE html PUBLIC "-//W3C//DTD XHTML 1.0 Transitional//EN" "http://www.w3.org/TR/xhtml1/DTD/xhtml1-transitional.dtd"> +<html xmlns="http://www.w3.org/1999/xhtml" +><head + ><meta http-equiv="Content-Type" content="text/html; charset=UTF-8" + /><title + >GADTRecords</title + ><link href="ocean.css" rel="stylesheet" type="text/css" title="Ocean" + /><script src="haddock-util.js" type="text/javascript" + ></script + ><script type="text/javascript" + >//<![CDATA[ +window.onload = function () {pageLoad();}; +//]]> +</script + ></head + ><body id="mini" + ><div id="module-header" + ><p class="caption" + >GADTRecords</p + ></div + ><div id="interface" + ><div class="top" + ><p class="src" + ><span class="keyword" + >data</span + > <a href="" target="main" + >H1</a + > a b</p + ></div + ></div + ></body + ></html +> diff --git a/tests/html-tests/tests/mini_Hash.html.ref b/tests/html-tests/tests/mini_Hash.html.ref new file mode 100644 index 00000000..1e6ad1a9 --- /dev/null +++ b/tests/html-tests/tests/mini_Hash.html.ref @@ -0,0 +1,74 @@ +<!DOCTYPE html PUBLIC "-//W3C//DTD XHTML 1.0 Transitional//EN" "http://www.w3.org/TR/xhtml1/DTD/xhtml1-transitional.dtd"> +<html xmlns="http://www.w3.org/1999/xhtml" +><head + ><meta http-equiv="Content-Type" content="text/html; charset=UTF-8" + /><title + >Hash</title + ><link href="ocean.css" rel="stylesheet" type="text/css" title="Ocean" + /><script src="haddock-util.js" type="text/javascript" + ></script + ><script type="text/javascript" + >//<![CDATA[ +window.onload = function () {pageLoad();}; +//]]> +</script + ></head + ><body id="mini" + ><div id="module-header" + ><p class="caption" + >Hash</p + ></div + ><div id="interface" + ><h1 + >The <code + >HashTable</code + > type +</h1 + ><div class="top" + ><p class="src" + ><span class="keyword" + >data</span + > <a href="" target="main" + >HashTable</a + > key val</p + ></div + ><h2 + >Operations on <code + >HashTable</code + >s +</h2 + ><div class="top" + ><p class="src" + ><a href="" target="main" + >new</a + ></p + ></div + ><div class="top" + ><p class="src" + ><a href="" target="main" + >insert</a + ></p + ></div + ><div class="top" + ><p class="src" + ><a href="" target="main" + >lookup</a + ></p + ></div + ><h1 + >The <code + >Hash</code + > class +</h1 + ><div class="top" + ><p class="src" + ><span class="keyword" + >class</span + > <a href="" target="main" + >Hash</a + > a</p + ></div + ></div + ></body + ></html +> diff --git a/tests/html-tests/tests/mini_ModuleWithWarning.html.ref b/tests/html-tests/tests/mini_ModuleWithWarning.html.ref new file mode 100644 index 00000000..19315a14 --- /dev/null +++ b/tests/html-tests/tests/mini_ModuleWithWarning.html.ref @@ -0,0 +1,31 @@ +<!DOCTYPE html PUBLIC "-//W3C//DTD XHTML 1.0 Transitional//EN" "http://www.w3.org/TR/xhtml1/DTD/xhtml1-transitional.dtd"> +<html xmlns="http://www.w3.org/1999/xhtml" +><head + ><meta http-equiv="Content-Type" content="text/html; charset=UTF-8" + /><title + >ModuleWithWarning</title + ><link href="ocean.css" rel="stylesheet" type="text/css" title="Ocean" + /><script src="haddock-util.js" type="text/javascript" + ></script + ><script type="text/javascript" + >//<![CDATA[ +window.onload = function () {pageLoad();}; +//]]> +</script + ></head + ><body id="mini" + ><div id="module-header" + ><p class="caption" + >ModuleWithWarning</p + ></div + ><div id="interface" + ><div class="top" + ><p class="src" + ><a href="" target="main" + >foo</a + ></p + ></div + ></div + ></body + ></html +> diff --git a/tests/html-tests/tests/mini_NamedDoc.html.ref b/tests/html-tests/tests/mini_NamedDoc.html.ref new file mode 100644 index 00000000..066bbc61 --- /dev/null +++ b/tests/html-tests/tests/mini_NamedDoc.html.ref @@ -0,0 +1,25 @@ +<!DOCTYPE html PUBLIC "-//W3C//DTD XHTML 1.0 Transitional//EN" "http://www.w3.org/TR/xhtml1/DTD/xhtml1-transitional.dtd"> +<html xmlns="http://www.w3.org/1999/xhtml" +><head + ><meta http-equiv="Content-Type" content="text/html; charset=UTF-8" + /><title + >NamedDoc</title + ><link href="ocean.css" rel="stylesheet" type="text/css" title="Ocean" + /><script src="haddock-util.js" type="text/javascript" + ></script + ><script type="text/javascript" + >//<![CDATA[ +window.onload = function () {pageLoad();}; +//]]> +</script + ></head + ><body id="mini" + ><div id="module-header" + ><p class="caption" + >NamedDoc</p + ></div + ><div id="interface" + ></div + ></body + ></html +> diff --git a/tests/html-tests/tests/mini_NoLayout.html.ref b/tests/html-tests/tests/mini_NoLayout.html.ref new file mode 100644 index 00000000..19562d70 --- /dev/null +++ b/tests/html-tests/tests/mini_NoLayout.html.ref @@ -0,0 +1,31 @@ +<!DOCTYPE html PUBLIC "-//W3C//DTD XHTML 1.0 Transitional//EN" "http://www.w3.org/TR/xhtml1/DTD/xhtml1-transitional.dtd"> +<html xmlns="http://www.w3.org/1999/xhtml" +><head + ><meta http-equiv="Content-Type" content="text/html; charset=UTF-8" + /><title + >NoLayout</title + ><link href="ocean.css" rel="stylesheet" type="text/css" title="Ocean" + /><script src="haddock-util.js" type="text/javascript" + ></script + ><script type="text/javascript" + >//<![CDATA[ +window.onload = function () {pageLoad();}; +//]]> +</script + ></head + ><body id="mini" + ><div id="module-header" + ><p class="caption" + >NoLayout</p + ></div + ><div id="interface" + ><div class="top" + ><p class="src" + ><a href="" target="main" + >g</a + ></p + ></div + ></div + ></body + ></html +> diff --git a/tests/html-tests/tests/mini_NonGreedy.html.ref b/tests/html-tests/tests/mini_NonGreedy.html.ref new file mode 100644 index 00000000..698c368e --- /dev/null +++ b/tests/html-tests/tests/mini_NonGreedy.html.ref @@ -0,0 +1,31 @@ +<!DOCTYPE html PUBLIC "-//W3C//DTD XHTML 1.0 Transitional//EN" "http://www.w3.org/TR/xhtml1/DTD/xhtml1-transitional.dtd"> +<html xmlns="http://www.w3.org/1999/xhtml" +><head + ><meta http-equiv="Content-Type" content="text/html; charset=UTF-8" + /><title + >NonGreedy</title + ><link href="ocean.css" rel="stylesheet" type="text/css" title="Ocean" + /><script src="haddock-util.js" type="text/javascript" + ></script + ><script type="text/javascript" + >//<![CDATA[ +window.onload = function () {pageLoad();}; +//]]> +</script + ></head + ><body id="mini" + ><div id="module-header" + ><p class="caption" + >NonGreedy</p + ></div + ><div id="interface" + ><div class="top" + ><p class="src" + ><a href="" target="main" + >f</a + ></p + ></div + ></div + ></body + ></html +> diff --git a/tests/html-tests/tests/mini_QuasiExpr.html.ref b/tests/html-tests/tests/mini_QuasiExpr.html.ref new file mode 100644 index 00000000..7dd9b829 --- /dev/null +++ b/tests/html-tests/tests/mini_QuasiExpr.html.ref @@ -0,0 +1,59 @@ +<!DOCTYPE html PUBLIC "-//W3C//DTD XHTML 1.0 Transitional//EN" "http://www.w3.org/TR/xhtml1/DTD/xhtml1-transitional.dtd"> +<html xmlns="http://www.w3.org/1999/xhtml" +><head + ><meta http-equiv="Content-Type" content="text/html; charset=UTF-8" + /><title + >QuasiExpr</title + ><link href="ocean.css" rel="stylesheet" type="text/css" title="Ocean" + /><script src="haddock-util.js" type="text/javascript" + ></script + ><script type="text/javascript" + >//<![CDATA[ +window.onload = function () {pageLoad();}; +//]]> +</script + ></head + ><body id="mini" + ><div id="module-header" + ><p class="caption" + >QuasiExpr</p + ></div + ><div id="interface" + ><div class="top" + ><p class="src" + ><span class="keyword" + >data</span + > <a href="" target="main" + >Expr</a + > </p + ></div + ><div class="top" + ><p class="src" + ><span class="keyword" + >data</span + > <a href="" target="main" + >BinOp</a + > </p + ></div + ><div class="top" + ><p class="src" + ><a href="" target="main" + >eval</a + ></p + ></div + ><div class="top" + ><p class="src" + ><a href="" target="main" + >expr</a + ></p + ></div + ><div class="top" + ><p class="src" + ><a href="" target="main" + >parseExprExp</a + ></p + ></div + ></div + ></body + ></html +> diff --git a/tests/html-tests/tests/mini_QuasiQuote.html.ref b/tests/html-tests/tests/mini_QuasiQuote.html.ref new file mode 100644 index 00000000..5dac6acc --- /dev/null +++ b/tests/html-tests/tests/mini_QuasiQuote.html.ref @@ -0,0 +1,31 @@ +<!DOCTYPE html PUBLIC "-//W3C//DTD XHTML 1.0 Transitional//EN" "http://www.w3.org/TR/xhtml1/DTD/xhtml1-transitional.dtd"> +<html xmlns="http://www.w3.org/1999/xhtml" +><head + ><meta http-equiv="Content-Type" content="text/html; charset=UTF-8" + /><title + >QuasiQuote</title + ><link href="ocean.css" rel="stylesheet" type="text/css" title="Ocean" + /><script src="haddock-util.js" type="text/javascript" + ></script + ><script type="text/javascript" + >//<![CDATA[ +window.onload = function () {pageLoad();}; +//]]> +</script + ></head + ><body id="mini" + ><div id="module-header" + ><p class="caption" + >QuasiQuote</p + ></div + ><div id="interface" + ><div class="top" + ><p class="src" + ><a href="" target="main" + >val</a + ></p + ></div + ></div + ></body + ></html +> diff --git a/tests/html-tests/tests/mini_TH.html.ref b/tests/html-tests/tests/mini_TH.html.ref new file mode 100644 index 00000000..d2ddbabc --- /dev/null +++ b/tests/html-tests/tests/mini_TH.html.ref @@ -0,0 +1,31 @@ +<!DOCTYPE html PUBLIC "-//W3C//DTD XHTML 1.0 Transitional//EN" "http://www.w3.org/TR/xhtml1/DTD/xhtml1-transitional.dtd"> +<html xmlns="http://www.w3.org/1999/xhtml" +><head + ><meta http-equiv="Content-Type" content="text/html; charset=UTF-8" + /><title + >TH</title + ><link href="ocean.css" rel="stylesheet" type="text/css" title="Ocean" + /><script src="haddock-util.js" type="text/javascript" + ></script + ><script type="text/javascript" + >//<![CDATA[ +window.onload = function () {pageLoad();}; +//]]> +</script + ></head + ><body id="mini" + ><div id="module-header" + ><p class="caption" + >TH</p + ></div + ><div id="interface" + ><div class="top" + ><p class="src" + ><a href="" target="main" + >decl</a + ></p + ></div + ></div + ></body + ></html +> diff --git a/tests/html-tests/tests/mini_TH2.html.ref b/tests/html-tests/tests/mini_TH2.html.ref new file mode 100644 index 00000000..2c9f1340 --- /dev/null +++ b/tests/html-tests/tests/mini_TH2.html.ref @@ -0,0 +1,31 @@ +<!DOCTYPE html PUBLIC "-//W3C//DTD XHTML 1.0 Transitional//EN" "http://www.w3.org/TR/xhtml1/DTD/xhtml1-transitional.dtd"> +<html xmlns="http://www.w3.org/1999/xhtml" +><head + ><meta http-equiv="Content-Type" content="text/html; charset=UTF-8" + /><title + >TH2</title + ><link href="ocean.css" rel="stylesheet" type="text/css" title="Ocean" + /><script src="haddock-util.js" type="text/javascript" + ></script + ><script type="text/javascript" + >//<![CDATA[ +window.onload = function () {pageLoad();}; +//]]> +</script + ></head + ><body id="mini" + ><div id="module-header" + ><p class="caption" + >TH2</p + ></div + ><div id="interface" + ><div class="top" + ><p class="src" + ><a href="" target="main" + >f</a + ></p + ></div + ></div + ></body + ></html +> diff --git a/tests/html-tests/tests/mini_Test.html.ref b/tests/html-tests/tests/mini_Test.html.ref new file mode 100644 index 00000000..26db2c0f --- /dev/null +++ b/tests/html-tests/tests/mini_Test.html.ref @@ -0,0 +1,269 @@ +<!DOCTYPE html PUBLIC "-//W3C//DTD XHTML 1.0 Transitional//EN" "http://www.w3.org/TR/xhtml1/DTD/xhtml1-transitional.dtd"> +<html xmlns="http://www.w3.org/1999/xhtml" +><head + ><meta http-equiv="Content-Type" content="text/html; charset=UTF-8" + /><title + >Test</title + ><link href="ocean.css" rel="stylesheet" type="text/css" title="Ocean" + /><script src="haddock-util.js" type="text/javascript" + ></script + ><script type="text/javascript" + >//<![CDATA[ +window.onload = function () {pageLoad();}; +//]]> +</script + ></head + ><body id="mini" + ><div id="module-header" + ><p class="caption" + >Test</p + ></div + ><div id="interface" + ><h1 + >Type declarations +</h1 + ><h2 + >Data types +</h2 + ><div class="top" + ><p class="src" + ><span class="keyword" + >data</span + > <a href="" target="main" + >T</a + > a b</p + ></div + ><div class="top" + ><p class="src" + ><span class="keyword" + >data</span + > <a href="" target="main" + >T2</a + > a b</p + ></div + ><div class="top" + ><p class="src" + ><span class="keyword" + >data</span + > <a href="" target="main" + >T3</a + > a b</p + ></div + ><div class="top" + ><p class="src" + ><span class="keyword" + >data</span + > <a href="" target="main" + >T4</a + > a b</p + ></div + ><div class="top" + ><p class="src" + ><span class="keyword" + >data</span + > <a href="" target="main" + >T5</a + > a b</p + ></div + ><div class="top" + ><p class="src" + ><span class="keyword" + >data</span + > <a href="" target="main" + >T6</a + > </p + ></div + ><div class="top" + ><p class="src" + ><span class="keyword" + >data</span + > <a href="" target="main" + >N1</a + > a</p + ></div + ><div class="top" + ><p class="src" + ><span class="keyword" + >data</span + > <a href="" target="main" + >N2</a + > a b</p + ></div + ><div class="top" + ><p class="src" + ><span class="keyword" + >data</span + > <a href="" target="main" + >N3</a + > a b</p + ></div + ><div class="top" + ><p class="src" + ><span class="keyword" + >data</span + > <a href="" target="main" + >N4</a + > a b</p + ></div + ><div class="top" + ><p class="src" + ><span class="keyword" + >data</span + > <a href="" target="main" + >N5</a + > a b</p + ></div + ><div class="top" + ><p class="src" + ><span class="keyword" + >data</span + > <a href="" target="main" + >N6</a + > a b</p + ></div + ><div class="top" + ><p class="src" + ><span class="keyword" + >data</span + > <a href="" target="main" + >N7</a + > a b</p + ></div + ><h2 + >Records +</h2 + ><div class="top" + ><p class="src" + ><span class="keyword" + >data</span + > <a href="" target="main" + >R</a + > </p + ></div + ><div class="top" + ><p class="src" + ><span class="keyword" + >data</span + > <a href="" target="main" + >R1</a + > </p + ></div + ><h1 + >Class declarations +</h1 + ><div class="top" + ><p class="src" + ><span class="keyword" + >class</span + > <a href="" target="main" + >C</a + > a</p + ></div + ><div class="top" + ><p class="src" + ><span class="keyword" + >class</span + > <a href="" target="main" + >D</a + > a</p + ></div + ><div class="top" + ><p class="src" + ><span class="keyword" + >class</span + > <a href="" target="main" + >E</a + > a</p + ></div + ><div class="top" + ><p class="src" + ><span class="keyword" + >class</span + > <a href="" target="main" + >F</a + > a</p + ></div + ><h1 + >Function types +</h1 + ><div class="top" + ><p class="src" + ><a href="" target="main" + >f</a + ></p + ></div + ><h1 + >Auxiliary stuff +</h1 + ><h1 + >A hidden module +</h1 + ><div class="top" + ><p class="src" + ><a href="" target="main" + >hidden</a + ></p + ></div + ><h1 + >A visible module +</h1 + ><h1 + >Existential / Universal types +</h1 + ><div class="top" + ><p class="src" + ><span class="keyword" + >data</span + > <a href="" target="main" + >Ex</a + > a</p + ></div + ><h1 + >Type signatures with argument docs +</h1 + ><div class="top" + ><p class="src" + ><a href="" target="main" + >k</a + ></p + ></div + ><div class="top" + ><p class="src" + ><a href="" target="main" + >l</a + ></p + ></div + ><div class="top" + ><p class="src" + ><a href="" target="main" + >m</a + ></p + ></div + ><h1 + >A section +</h1 + ><h2 + >A subsection +</h2 + ><div class="top" + ><p class="src" + ><a href="" target="main" + >f'</a + ></p + ></div + ><div class="top" + ><p class="src" + ><a href="" target="main" + >withType</a + ></p + ></div + ><div class="top" + ><p class="src" + ><a href="" target="main" + >withoutType</a + ></p + ></div + ></div + ></body + ></html +> diff --git a/tests/html-tests/tests/mini_Ticket112.html.ref b/tests/html-tests/tests/mini_Ticket112.html.ref new file mode 100644 index 00000000..68a0a5e5 --- /dev/null +++ b/tests/html-tests/tests/mini_Ticket112.html.ref @@ -0,0 +1,31 @@ +<!DOCTYPE html PUBLIC "-//W3C//DTD XHTML 1.0 Transitional//EN" "http://www.w3.org/TR/xhtml1/DTD/xhtml1-transitional.dtd"> +<html xmlns="http://www.w3.org/1999/xhtml" +><head + ><meta http-equiv="Content-Type" content="text/html; charset=UTF-8" + /><title + >Ticket112</title + ><link href="ocean.css" rel="stylesheet" type="text/css" title="Ocean" + /><script src="haddock-util.js" type="text/javascript" + ></script + ><script type="text/javascript" + >//<![CDATA[ +window.onload = function () {pageLoad();}; +//]]> +</script + ></head + ><body id="mini" + ><div id="module-header" + ><p class="caption" + >Ticket112</p + ></div + ><div id="interface" + ><div class="top" + ><p class="src" + ><a href="" target="main" + >f</a + ></p + ></div + ></div + ></body + ></html +> diff --git a/tests/html-tests/tests/mini_Ticket61.html.ref b/tests/html-tests/tests/mini_Ticket61.html.ref new file mode 100644 index 00000000..a73fefca --- /dev/null +++ b/tests/html-tests/tests/mini_Ticket61.html.ref @@ -0,0 +1,33 @@ +<!DOCTYPE html PUBLIC "-//W3C//DTD XHTML 1.0 Transitional//EN" "http://www.w3.org/TR/xhtml1/DTD/xhtml1-transitional.dtd"> +<html xmlns="http://www.w3.org/1999/xhtml" +><head + ><meta http-equiv="Content-Type" content="text/html; charset=UTF-8" + /><title + >Ticket61</title + ><link href="ocean.css" rel="stylesheet" type="text/css" title="Ocean" + /><script src="haddock-util.js" type="text/javascript" + ></script + ><script type="text/javascript" + >//<![CDATA[ +window.onload = function () {pageLoad();}; +//]]> +</script + ></head + ><body id="mini" + ><div id="module-header" + ><p class="caption" + >Ticket61</p + ></div + ><div id="interface" + ><div class="top" + ><p class="src" + ><span class="keyword" + >class</span + > <a href="" target="main" + >C</a + > a</p + ></div + ></div + ></body + ></html +> diff --git a/tests/html-tests/tests/mini_Ticket75.html.ref b/tests/html-tests/tests/mini_Ticket75.html.ref new file mode 100644 index 00000000..75ce882c --- /dev/null +++ b/tests/html-tests/tests/mini_Ticket75.html.ref @@ -0,0 +1,39 @@ +<!DOCTYPE html PUBLIC "-//W3C//DTD XHTML 1.0 Transitional//EN" "http://www.w3.org/TR/xhtml1/DTD/xhtml1-transitional.dtd"> +<html xmlns="http://www.w3.org/1999/xhtml" +><head + ><meta http-equiv="Content-Type" content="text/html; charset=UTF-8" + /><title + >Ticket75</title + ><link href="ocean.css" rel="stylesheet" type="text/css" title="Ocean" + /><script src="haddock-util.js" type="text/javascript" + ></script + ><script type="text/javascript" + >//<![CDATA[ +window.onload = function () {pageLoad();}; +//]]> +</script + ></head + ><body id="mini" + ><div id="module-header" + ><p class="caption" + >Ticket75</p + ></div + ><div id="interface" + ><div class="top" + ><p class="src" + ><span class="keyword" + >data</span + > a <a href="" target="main" + >:-</a + > b</p + ></div + ><div class="top" + ><p class="src" + ><a href="" target="main" + >f</a + ></p + ></div + ></div + ></body + ></html +> diff --git a/tests/html-tests/tests/mini_TypeFamilies.html.ref b/tests/html-tests/tests/mini_TypeFamilies.html.ref new file mode 100644 index 00000000..0cf39c88 --- /dev/null +++ b/tests/html-tests/tests/mini_TypeFamilies.html.ref @@ -0,0 +1,55 @@ +<!DOCTYPE html PUBLIC "-//W3C//DTD XHTML 1.0 Transitional//EN" "http://www.w3.org/TR/xhtml1/DTD/xhtml1-transitional.dtd"> +<html xmlns="http://www.w3.org/1999/xhtml" +><head + ><meta http-equiv="Content-Type" content="text/html; charset=UTF-8" + /><title + >TypeFamilies</title + ><link href="ocean.css" rel="stylesheet" type="text/css" title="Ocean" + /><script src="haddock-util.js" type="text/javascript" + ></script + ><script type="text/javascript" + >//<![CDATA[ +window.onload = function () {pageLoad();}; +//]]> +</script + ></head + ><body id="mini" + ><div id="module-header" + ><p class="caption" + >TypeFamilies</p + ></div + ><div id="interface" + ><div class="top" + ><p class="src" + ><span class="keyword" + >type family</span + > <a href="" + >G</a + > a :: *</p + ></div + ><div class="top" + ><p class="src" + ><span class="keyword" + >class</span + > <a href="" target="main" + >A</a + > a</p + ></div + ><div class="top" + ><p class="src" + ><span class="keyword" + >type family</span + > <a href="" + >F</a + > a </p + ></div + ><div class="top" + ><p class="src" + ><a href="" target="main" + >g</a + ></p + ></div + ></div + ></body + ></html +> diff --git a/tests/html-tests/tests/mini_TypeOperators.html.ref b/tests/html-tests/tests/mini_TypeOperators.html.ref new file mode 100644 index 00000000..f70a0fae --- /dev/null +++ b/tests/html-tests/tests/mini_TypeOperators.html.ref @@ -0,0 +1,74 @@ +<!DOCTYPE html PUBLIC "-//W3C//DTD XHTML 1.0 Transitional//EN" "http://www.w3.org/TR/xhtml1/DTD/xhtml1-transitional.dtd"> +<html xmlns="http://www.w3.org/1999/xhtml" +><head + ><meta http-equiv="Content-Type" content="text/html; charset=UTF-8" + /><title + >TypeOperators</title + ><link href="ocean.css" rel="stylesheet" type="text/css" title="Ocean" + /><script src="haddock-util.js" type="text/javascript" + ></script + ><script type="text/javascript" + >//<![CDATA[ +window.onload = function () {pageLoad();}; +//]]> +</script + ></head + ><body id="mini" + ><div id="module-header" + ><p class="caption" + >TypeOperators</p + ></div + ><div id="interface" + ><h1 + >stuff +</h1 + ><div class="top" + ><p class="src" + ><span class="keyword" + >data</span + > a <a href="" target="main" + >:-:</a + > b</p + ></div + ><div class="top" + ><p class="src" + ><span class="keyword" + >data</span + > (a <a href="" target="main" + >:+:</a + > b) c</p + ></div + ><div class="top" + ><p class="src" + ><span class="keyword" + >data</span + > <a href="" target="main" + >Op</a + > a b</p + ></div + ><div class="top" + ><p class="src" + ><span class="keyword" + >data</span + > <a href="" target="main" + >O</a + > g f a</p + ></div + ><div class="top" + ><p class="src" + ><a href="" target="main" + >biO</a + ></p + ></div + ><div class="top" + ><p class="src" + ><span class="keyword" + >data</span + > <a href="" target="main" + >Flip</a + > (~>) b a</p + ></div + ></div + ></body + ></html +> diff --git a/tests/html-tests/tests/mini_Unicode.html.ref b/tests/html-tests/tests/mini_Unicode.html.ref new file mode 100644 index 00000000..55336980 --- /dev/null +++ b/tests/html-tests/tests/mini_Unicode.html.ref @@ -0,0 +1,31 @@ +<!DOCTYPE html PUBLIC "-//W3C//DTD XHTML 1.0 Transitional//EN" "http://www.w3.org/TR/xhtml1/DTD/xhtml1-transitional.dtd"> +<html xmlns="http://www.w3.org/1999/xhtml" +><head + ><meta http-equiv="Content-Type" content="text/html; charset=UTF-8" + /><title + >Unicode</title + ><link href="ocean.css" rel="stylesheet" type="text/css" title="Ocean" + /><script src="haddock-util.js" type="text/javascript" + ></script + ><script type="text/javascript" + >//<![CDATA[ +window.onload = function () {pageLoad();}; +//]]> +</script + ></head + ><body id="mini" + ><div id="module-header" + ><p class="caption" + >Unicode</p + ></div + ><div id="interface" + ><div class="top" + ><p class="src" + ><a href="" target="main" + >x</a + ></p + ></div + ></div + ></body + ></html +> diff --git a/tests/html-tests/tests/mini_Visible.html.ref b/tests/html-tests/tests/mini_Visible.html.ref new file mode 100644 index 00000000..976a30c5 --- /dev/null +++ b/tests/html-tests/tests/mini_Visible.html.ref @@ -0,0 +1,31 @@ +<!DOCTYPE html PUBLIC "-//W3C//DTD XHTML 1.0 Transitional//EN" "http://www.w3.org/TR/xhtml1/DTD/xhtml1-transitional.dtd"> +<html xmlns="http://www.w3.org/1999/xhtml" +><head + ><meta http-equiv="Content-Type" content="text/html; charset=UTF-8" + /><title + >Visible</title + ><link href="ocean.css" rel="stylesheet" type="text/css" title="Ocean" + /><script src="haddock-util.js" type="text/javascript" + ></script + ><script type="text/javascript" + >//<![CDATA[ +window.onload = function () {pageLoad();}; +//]]> +</script + ></head + ><body id="mini" + ><div id="module-header" + ><p class="caption" + >Visible</p + ></div + ><div id="interface" + ><div class="top" + ><p class="src" + ><a href="" target="main" + >visible</a + ></p + ></div + ></div + ></body + ></html +> diff --git a/tests/unit-tests/.ghci b/tests/unit-tests/.ghci new file mode 100644 index 00000000..10563664 --- /dev/null +++ b/tests/unit-tests/.ghci @@ -0,0 +1 @@ +:set -i../../src -i../../dist/build/autogen -i../../dist/build/haddock/haddock-tmp/ -packageghc -optP-include -optP../../dist/build/autogen/cabal_macros.h -XCPP -XDeriveDataTypeable -XScopedTypeVariables -XMagicHash diff --git a/tests/unit-tests/parsetests.hs b/tests/unit-tests/parsetests.hs index e0645401..7180a79e 100644 --- a/tests/unit-tests/parsetests.hs +++ b/tests/unit-tests/parsetests.hs @@ -1,3 +1,5 @@ +{-# LANGUAGE StandaloneDeriving, FlexibleInstances, UndecidableInstances, IncoherentInstances #-} +{-# OPTIONS_GHC -fno-warn-orphans #-} module Main (main) where import Test.HUnit @@ -6,9 +8,13 @@ import DynFlags (defaultDynFlags) import Haddock.Lex (tokenise) import Haddock.Parse (parseParas) import Haddock.Types +import Outputable -instance Show RdrName where - show x = "RdrName" +instance Outputable a => Show a where + show = showSDoc . ppr + +deriving instance Show a => Show (Doc a) +deriving instance Eq a =>Eq (Doc a) data ParseTest = ParseTest { input :: String @@ -50,13 +56,14 @@ tests = [ ] +main :: IO () main = do _ <- runTestTT $ TestList $ map toTestCase tests return (); where toTestCase :: ParseTest -> Test - toTestCase (ParseTest input result) = TestCase $ assertEqual input result (parse input) + toTestCase (ParseTest s r) = TestCase $ assertEqual s r (parse s) parse :: String -> Maybe (Doc RdrName) - parse input = parseParas $ tokenise defaultDynFlags input (0,0) + parse s = parseParas $ tokenise (defaultDynFlags undefined) s (0,0) diff --git a/tests/unit-tests/runparsetests.sh b/tests/unit-tests/runparsetests.sh index 1dae69c2..ead0ccf5 100644..100755 --- a/tests/unit-tests/runparsetests.sh +++ b/tests/unit-tests/runparsetests.sh @@ -1,15 +1,15 @@ #!/bin/sh cd `dirname $0` -runhaskell -hide-all-packages -cpp \ - -packagecontainers \ - -packagearray \ - -packagebase \ +runhaskell \ + -i../../src \ + -i../../dist/build/autogen \ + -i../../dist/build/haddock/haddock-tmp/ \ -packageghc \ - -packagexhtml \ - -packageghc-paths \ - -packageHUnit \ - -i../../dist/build/ \ - -i../../src/ \ - -optP-include -optP../../dist/build/autogen/cabal_macros.h \ + -optP-include \ + -optP../../dist/build/autogen/cabal_macros.h \ + -XCPP \ + -XDeriveDataTypeable \ + -XScopedTypeVariables \ + -XMagicHash \ parsetests.hs |