aboutsummaryrefslogtreecommitdiff
path: root/html-test/src
diff options
context:
space:
mode:
authorKazu Yamamoto <kazu@iij.ad.jp>2013-02-01 11:59:24 +0900
committerKazu Yamamoto <kazu@iij.ad.jp>2013-02-01 11:59:24 +0900
commit8d4c94ca5a969a5ebbb791939fb0195dc672429e (patch)
tree560a944a7105cd715f9acba46790bd7e1a77f82f /html-test/src
parent266a20afd2d27f28bbb62839ebc3f70bd83bfcce (diff)
parent3d25ea2929a9a9bd0768339b8ac5fd1b7c4670ad (diff)
Merge branch 'ghc-7.6' into ghc-7.6-merge-2
Conflicts: haddock.cabal src/Haddock/Interface/AttachInstances.hs src/Haddock/Interface/Create.hs src/Haddock/Interface/LexParseRn.hs src/Haddock/InterfaceFile.hs src/Haddock/Types.hs Only GHC HEAD can compile this. GHC 7.6.x cannot compile this. Some test fail.
Diffstat (limited to 'html-test/src')
-rw-r--r--html-test/src/A.hs17
-rw-r--r--html-test/src/AdvanceTypes.hs9
-rw-r--r--html-test/src/B.hs8
-rw-r--r--html-test/src/Bug1.hs6
-rw-r--r--html-test/src/Bug2.hs4
-rw-r--r--html-test/src/Bug3.hs6
-rw-r--r--html-test/src/Bug4.hs5
-rw-r--r--html-test/src/Bug6.hs23
-rw-r--r--html-test/src/Bug7.hs12
-rw-r--r--html-test/src/Bug8.hs14
-rw-r--r--html-test/src/BugDeprecated.hs18
-rw-r--r--html-test/src/BugExportHeadings.hs29
-rw-r--r--html-test/src/Bugs.hs3
-rw-r--r--html-test/src/CrossPackageDocs.hs4
-rw-r--r--html-test/src/DeprecatedClass.hs15
-rw-r--r--html-test/src/DeprecatedData.hs15
-rw-r--r--html-test/src/DeprecatedFunction.hs10
-rw-r--r--html-test/src/DeprecatedFunction2.hs6
-rw-r--r--html-test/src/DeprecatedFunction3.hs6
-rw-r--r--html-test/src/DeprecatedModule.hs5
-rw-r--r--html-test/src/DeprecatedModule2.hs4
-rw-r--r--html-test/src/DeprecatedNewtype.hs10
-rw-r--r--html-test/src/DeprecatedReExport.hs16
-rw-r--r--html-test/src/DeprecatedRecord.hs9
-rw-r--r--html-test/src/DeprecatedTypeFamily.hs9
-rw-r--r--html-test/src/DeprecatedTypeSynonym.hs9
-rw-r--r--html-test/src/DeprecationMessageParseError.hs12
-rw-r--r--html-test/src/Examples.hs39
-rw-r--r--html-test/src/FunArgs.hs16
-rw-r--r--html-test/src/GADTRecords.hs12
-rw-r--r--html-test/src/Hash.hs51
-rw-r--r--html-test/src/Hidden.hs6
-rw-r--r--html-test/src/HiddenInstances.hs35
-rw-r--r--html-test/src/HiddenInstancesA.hs17
-rw-r--r--html-test/src/HiddenInstancesB.hs2
-rw-r--r--html-test/src/Hyperlinks.hs8
-rw-r--r--html-test/src/IgnoreExports.hs10
-rw-r--r--html-test/src/ModuleWithWarning.hs5
-rw-r--r--html-test/src/NamedDoc.hs4
-rw-r--r--html-test/src/NoLayout.hs12
-rw-r--r--html-test/src/NonGreedy.hs5
-rw-r--r--html-test/src/Properties.hs9
-rw-r--r--html-test/src/PruneWithWarning.hs15
-rw-r--r--html-test/src/QuasiExpr.hs34
-rw-r--r--html-test/src/QuasiQuote.hs9
-rw-r--r--html-test/src/SpuriousSuperclassConstraints.hs30
-rw-r--r--html-test/src/TH.hs8
-rw-r--r--html-test/src/TH2.hs7
-rw-r--r--html-test/src/Test.hs422
-rw-r--r--html-test/src/Ticket112.hs9
-rw-r--r--html-test/src/Ticket61.hs3
-rw-r--r--html-test/src/Ticket61_Hidden.hs7
-rw-r--r--html-test/src/Ticket75.hs7
-rw-r--r--html-test/src/TypeFamilies.hs28
-rw-r--r--html-test/src/TypeOperators.hs20
-rw-r--r--html-test/src/Unicode.hs.disabled6
-rw-r--r--html-test/src/Visible.hs3
57 files changed, 1123 insertions, 0 deletions
diff --git a/html-test/src/A.hs b/html-test/src/A.hs
new file mode 100644
index 00000000..606b0865
--- /dev/null
+++ b/html-test/src/A.hs
@@ -0,0 +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/html-test/src/AdvanceTypes.hs b/html-test/src/AdvanceTypes.hs
new file mode 100644
index 00000000..939fdf07
--- /dev/null
+++ b/html-test/src/AdvanceTypes.hs
@@ -0,0 +1,9 @@
+{-# LANGUAGE DataKinds #-}
+{-# LANGUAGE GADTs #-}
+{-# LANGUAGE KindSignatures #-}
+{-# LANGUAGE TypeOperators #-}
+module AdvanceTypes where
+
+data Pattern :: [*] -> * where
+ Nil :: Pattern '[]
+ Cons :: Maybe h -> Pattern t -> Pattern (h ': t)
diff --git a/html-test/src/B.hs b/html-test/src/B.hs
new file mode 100644
index 00000000..5fd69acd
--- /dev/null
+++ b/html-test/src/B.hs
@@ -0,0 +1,8 @@
+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'.
+-- Module link: "Prelude".
+test :: Int
+test = 1
diff --git a/html-test/src/Bug1.hs b/html-test/src/Bug1.hs
new file mode 100644
index 00000000..af1ed4d3
--- /dev/null
+++ b/html-test/src/Bug1.hs
@@ -0,0 +1,6 @@
+module Bug1 where
+
+-- | We should have different anchors for constructors and types\/classes. This
+-- hyperlink should point to the type constructor by default: 'T'.
+data T = T
+
diff --git a/html-test/src/Bug2.hs b/html-test/src/Bug2.hs
new file mode 100644
index 00000000..9121922e
--- /dev/null
+++ b/html-test/src/Bug2.hs
@@ -0,0 +1,4 @@
+module Bug2 ( x ) where
+import B
+x :: A
+x = A
diff --git a/html-test/src/Bug3.hs b/html-test/src/Bug3.hs
new file mode 100644
index 00000000..67e57892
--- /dev/null
+++ b/html-test/src/Bug3.hs
@@ -0,0 +1,6 @@
+module Bug3 where
+
+-- | /multi-line
+-- emphasis/
+foo :: Int
+foo = undefined
diff --git a/html-test/src/Bug4.hs b/html-test/src/Bug4.hs
new file mode 100644
index 00000000..425a77aa
--- /dev/null
+++ b/html-test/src/Bug4.hs
@@ -0,0 +1,5 @@
+module Bug4 where
+-- | don't use apostrophe's in the wrong place's
+foo :: Int
+foo = undefined
+
diff --git a/html-test/src/Bug6.hs b/html-test/src/Bug6.hs
new file mode 100644
index 00000000..17411f31
--- /dev/null
+++ b/html-test/src/Bug6.hs
@@ -0,0 +1,23 @@
+-- | Exporting records.
+module Bug6( A(A), B(B), b, C(C,c1,c2), D(D,d1), E(E) ) where
+
+-- |
+-- This record is exported without its field
+data A = A { a :: Int }
+
+-- |
+-- .. with its field, but the field is named separately in the export list
+-- (the field isn't documented separately since it is already documented here)
+data B = B { b :: Int }
+
+-- |
+-- .. with fields names as subordinate names in the export
+data C = C { c1 :: Int, c2 :: Int }
+
+-- |
+-- .. with only some of the fields exported (we can't handle this one -
+-- how do we render the declaration?)
+data D = D { d1 :: Int, d2 :: Int }
+
+-- | a newtype with a field
+newtype E = E { e :: Int }
diff --git a/html-test/src/Bug7.hs b/html-test/src/Bug7.hs
new file mode 100644
index 00000000..8cf57914
--- /dev/null
+++ b/html-test/src/Bug7.hs
@@ -0,0 +1,12 @@
+-- | This module caused a duplicate instance in the documentation for the Foo
+-- type.
+module Bug7 where
+
+-- | The Foo datatype
+data Foo = Foo
+
+-- | The Bar class
+class Bar x y
+
+-- | Just one instance
+instance Bar Foo Foo
diff --git a/html-test/src/Bug8.hs b/html-test/src/Bug8.hs
new file mode 100644
index 00000000..18df63c8
--- /dev/null
+++ b/html-test/src/Bug8.hs
@@ -0,0 +1,14 @@
+module Bug8 where
+
+infix -->
+infix --->
+
+data Typ = Type (String,[Typ])
+ | TFree (String, [String])
+
+x --> y = Type("fun",[s,t])
+(--->) = flip $ foldr (-->)
+
+s = undefined
+t = undefined
+main = undefined
diff --git a/html-test/src/BugDeprecated.hs b/html-test/src/BugDeprecated.hs
new file mode 100644
index 00000000..0f7ac2eb
--- /dev/null
+++ b/html-test/src/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/html-test/src/BugExportHeadings.hs b/html-test/src/BugExportHeadings.hs
new file mode 100644
index 00000000..a5493a08
--- /dev/null
+++ b/html-test/src/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/html-test/src/Bugs.hs b/html-test/src/Bugs.hs
new file mode 100644
index 00000000..8e1f0079
--- /dev/null
+++ b/html-test/src/Bugs.hs
@@ -0,0 +1,3 @@
+module Bugs where
+
+data A a = A a (a -> Int)
diff --git a/html-test/src/CrossPackageDocs.hs b/html-test/src/CrossPackageDocs.hs
new file mode 100644
index 00000000..4d529f79
--- /dev/null
+++ b/html-test/src/CrossPackageDocs.hs
@@ -0,0 +1,4 @@
+module CrossPackageDocs (map, IsString(..), runInteractiveProcess) where
+
+import System.Process
+import Data.String
diff --git a/html-test/src/DeprecatedClass.hs b/html-test/src/DeprecatedClass.hs
new file mode 100644
index 00000000..018904ab
--- /dev/null
+++ b/html-test/src/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/html-test/src/DeprecatedData.hs b/html-test/src/DeprecatedData.hs
new file mode 100644
index 00000000..c40ba122
--- /dev/null
+++ b/html-test/src/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/html-test/src/DeprecatedFunction.hs b/html-test/src/DeprecatedFunction.hs
new file mode 100644
index 00000000..8d626435
--- /dev/null
+++ b/html-test/src/DeprecatedFunction.hs
@@ -0,0 +1,10 @@
+module DeprecatedFunction where
+
+-- | some documentation for foo
+foo :: Int
+foo = 23
+{-# DEPRECATED foo "use `bar` instead" #-}
+
+-- | some documentation for bar
+bar :: Int
+bar = 42
diff --git a/html-test/src/DeprecatedFunction2.hs b/html-test/src/DeprecatedFunction2.hs
new file mode 100644
index 00000000..bdbbf95c
--- /dev/null
+++ b/html-test/src/DeprecatedFunction2.hs
@@ -0,0 +1,6 @@
+module DeprecatedFunction2 where
+
+
+foo :: Int
+foo = 23
+{-# DEPRECATED foo "use bar instead" #-}
diff --git a/html-test/src/DeprecatedFunction3.hs b/html-test/src/DeprecatedFunction3.hs
new file mode 100644
index 00000000..ca719bda
--- /dev/null
+++ b/html-test/src/DeprecatedFunction3.hs
@@ -0,0 +1,6 @@
+module DeprecatedFunction3 where
+
+
+
+foo = 23
+{-# DEPRECATED foo "use bar instead" #-}
diff --git a/html-test/src/DeprecatedModule.hs b/html-test/src/DeprecatedModule.hs
new file mode 100644
index 00000000..369dba4f
--- /dev/null
+++ b/html-test/src/DeprecatedModule.hs
@@ -0,0 +1,5 @@
+-- | Documentation for "DeprecatedModule".
+module DeprecatedModule {-# DEPRECATED "Use \"Foo\" instead" #-} where
+
+foo :: Int
+foo = 23
diff --git a/html-test/src/DeprecatedModule2.hs b/html-test/src/DeprecatedModule2.hs
new file mode 100644
index 00000000..94185297
--- /dev/null
+++ b/html-test/src/DeprecatedModule2.hs
@@ -0,0 +1,4 @@
+module DeprecatedModule2 {-# DEPRECATED "Use Foo instead" #-} where
+
+foo :: Int
+foo = 23
diff --git a/html-test/src/DeprecatedNewtype.hs b/html-test/src/DeprecatedNewtype.hs
new file mode 100644
index 00000000..254f1f55
--- /dev/null
+++ b/html-test/src/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/html-test/src/DeprecatedReExport.hs b/html-test/src/DeprecatedReExport.hs
new file mode 100644
index 00000000..f851e2ff
--- /dev/null
+++ b/html-test/src/DeprecatedReExport.hs
@@ -0,0 +1,16 @@
+-- |
+-- What is tested here:
+--
+-- * Deprecation messages are shown for re-exported items.
+--
+module DeprecatedReExport (
+-- * Re-exported from an other module
+ foo
+-- * Re-exported from an other package
+-- | Not yet working, see <http://trac.haskell.org/haddock/ticket/223>
+-- , isEmptyChan
+,
+) where
+
+import DeprecatedFunction
+import Control.Concurrent.Chan
diff --git a/html-test/src/DeprecatedRecord.hs b/html-test/src/DeprecatedRecord.hs
new file mode 100644
index 00000000..d44499e7
--- /dev/null
+++ b/html-test/src/DeprecatedRecord.hs
@@ -0,0 +1,9 @@
+module DeprecatedRecord where
+
+-- | type Foo
+data Foo = Foo {
+ fooName :: String -- ^ some name
+, fooValue :: Int -- ^ some value
+}
+
+{-# DEPRECATED fooValue "do not use this" #-}
diff --git a/html-test/src/DeprecatedTypeFamily.hs b/html-test/src/DeprecatedTypeFamily.hs
new file mode 100644
index 00000000..70473bb8
--- /dev/null
+++ b/html-test/src/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/html-test/src/DeprecatedTypeSynonym.hs b/html-test/src/DeprecatedTypeSynonym.hs
new file mode 100644
index 00000000..34df47da
--- /dev/null
+++ b/html-test/src/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/html-test/src/DeprecationMessageParseError.hs b/html-test/src/DeprecationMessageParseError.hs
new file mode 100644
index 00000000..2f8fb492
--- /dev/null
+++ b/html-test/src/DeprecationMessageParseError.hs
@@ -0,0 +1,12 @@
+-- |
+-- What is tested here:
+--
+-- * If parsing of a deprecation message fails, the message is included
+-- verbatim.
+--
+module DeprecationMessageParseError where
+
+-- | some documentation for foo
+foo :: Int
+foo = 23
+{-# DEPRECATED foo "use @bar instead" #-}
diff --git a/html-test/src/Examples.hs b/html-test/src/Examples.hs
new file mode 100644
index 00000000..c8c450f1
--- /dev/null
+++ b/html-test/src/Examples.hs
@@ -0,0 +1,39 @@
+module Examples where
+
+-- | Fibonacci number of given 'Integer'.
+--
+-- Examples:
+--
+-- >>> fib 5
+-- 5
+-- >>> fib 10
+-- 55
+--
+-- >>> fib 10
+-- 55
+--
+-- One more Example:
+--
+-- >>> fib 5
+-- 5
+--
+-- One more Example:
+--
+-- >>> fib 5
+-- 5
+--
+-- Example with an import:
+--
+-- >>> import Data.Char
+-- >>> isSpace 'a'
+-- False
+--
+-- >>> putStrLn "foo\n\nbar"
+-- foo
+-- <BLANKLINE>
+-- bar
+--
+fib :: Integer -> Integer
+fib 0 = 0
+fib 1 = 1
+fib n = fib (n - 1) + fib (n - 2)
diff --git a/html-test/src/FunArgs.hs b/html-test/src/FunArgs.hs
new file mode 100644
index 00000000..b34d84b7
--- /dev/null
+++ b/html-test/src/FunArgs.hs
@@ -0,0 +1,16 @@
+module FunArgs where
+
+f :: forall a. Ord a
+ => Int -- ^ First argument
+ -> a -- ^ Second argument
+ -> Bool -- ^ Third argument
+ -> (a -> a) -- ^ Fourth argument
+ -> () -- ^ Result
+f = undefined
+
+
+g :: a -- ^ First argument
+ -> b -- ^ Second argument
+ -> c -- ^ Third argument
+ -> d -- ^ Result
+g = undefined
diff --git a/html-test/src/GADTRecords.hs b/html-test/src/GADTRecords.hs
new file mode 100644
index 00000000..c77810ad
--- /dev/null
+++ b/html-test/src/GADTRecords.hs
@@ -0,0 +1,12 @@
+{-# LANGUAGE GADTs #-}
+module GADTRecords (H1(..)) where
+
+-- | h1
+data H1 a b where
+ C1 :: H1 a b
+ C2 :: Ord a => [a] -> H1 a a
+ C3 { field :: Int -- ^ hello docs
+ } :: H1 Int Int
+ C4 { field2 :: a -- ^ hello2 docs
+ } :: H1 Int a
+
diff --git a/html-test/src/Hash.hs b/html-test/src/Hash.hs
new file mode 100644
index 00000000..343b69e9
--- /dev/null
+++ b/html-test/src/Hash.hs
@@ -0,0 +1,51 @@
+{- |
+ Implementation of fixed-size hash tables, with a type
+ class for constructing hash values for structured types.
+-}
+module Hash (
+ -- * The @HashTable@ type
+ HashTable,
+
+ -- ** Operations on @HashTable@s
+ new, insert, lookup,
+
+ -- * The @Hash@ class
+ Hash(..),
+ ) where
+
+import Data.Array
+import Prelude hiding (lookup)
+
+-- | A hash table with keys of type @key@ and values of type @val@.
+-- The type @key@ should be an instance of 'Eq'.
+data HashTable key val = HashTable Int (Array Int [(key,val)])
+
+-- | Builds a new hash table with a given size
+new :: (Eq key, Hash key) => Int -> IO (HashTable key val)
+new = undefined
+
+-- | Inserts a new element into the hash table
+insert :: (Eq key, Hash key) => key -> val -> IO ()
+insert = undefined
+
+-- | Looks up a key in the hash table, returns @'Just' val@ if the key
+-- was found, or 'Nothing' otherwise.
+lookup :: Hash key => key -> IO (Maybe val)
+lookup = undefined
+
+-- | A class of types which can be hashed.
+class Hash a where
+ -- | hashes the value of type @a@ into an 'Int'
+ hash :: a -> Int
+
+instance Hash Int where
+ hash = id
+
+instance Hash Float where
+ hash = trunc
+
+instance (Hash a, Hash b) => Hash (a,b) where
+ hash (a,b) = hash a `xor` hash b
+
+trunc = undefined
+xor = undefined
diff --git a/html-test/src/Hidden.hs b/html-test/src/Hidden.hs
new file mode 100644
index 00000000..896da648
--- /dev/null
+++ b/html-test/src/Hidden.hs
@@ -0,0 +1,6 @@
+{-# OPTIONS_HADDOCK hide #-}
+
+module Hidden where
+
+hidden :: Int -> Int
+hidden a = a
diff --git a/html-test/src/HiddenInstances.hs b/html-test/src/HiddenInstances.hs
new file mode 100644
index 00000000..99a6c2fd
--- /dev/null
+++ b/html-test/src/HiddenInstances.hs
@@ -0,0 +1,35 @@
+-- http://trac.haskell.org/haddock/ticket/37
+module HiddenInstances (VisibleClass, VisibleData) where
+
+-- | Should be visible
+class VisibleClass a
+
+-- | Should *not* be visible
+class HiddenClass a
+
+-- | Should *not* be visible
+data HiddenData = HiddenData
+
+-- | Should be visible
+data VisibleData = VisibleData
+
+-- | Should be visible
+instance VisibleClass Int
+
+-- | Should be visible
+instance VisibleClass VisibleData
+
+-- | Should be visible
+instance Num VisibleData
+
+-- | Should *not* be visible
+instance VisibleClass HiddenData
+
+-- | Should *not* be visible
+instance HiddenClass Int
+
+-- | Should *not* be visible
+instance HiddenClass VisibleData
+
+-- | Should *not* be visible
+instance HiddenClass HiddenData
diff --git a/html-test/src/HiddenInstancesA.hs b/html-test/src/HiddenInstancesA.hs
new file mode 100644
index 00000000..f1775208
--- /dev/null
+++ b/html-test/src/HiddenInstancesA.hs
@@ -0,0 +1,17 @@
+{-# OPTIONS_HADDOCK hide #-}
+module HiddenInstancesA where
+
+-- | Should be visible
+class Foo a
+
+-- | Should be visible
+data Bar
+
+-- | Should be visible
+instance Foo Bar
+
+-- | Should *not* be visible
+data Baz
+
+-- | Should *not* be visible
+instance Foo Baz
diff --git a/html-test/src/HiddenInstancesB.hs b/html-test/src/HiddenInstancesB.hs
new file mode 100644
index 00000000..eabf0637
--- /dev/null
+++ b/html-test/src/HiddenInstancesB.hs
@@ -0,0 +1,2 @@
+module HiddenInstancesB (Foo, Bar) where
+import HiddenInstancesA
diff --git a/html-test/src/Hyperlinks.hs b/html-test/src/Hyperlinks.hs
new file mode 100644
index 00000000..34e64448
--- /dev/null
+++ b/html-test/src/Hyperlinks.hs
@@ -0,0 +1,8 @@
+module Hyperlinks where
+
+-- |
+-- A plain URL: <http://example.com/>
+--
+-- A URL with a label: <http://example.com/ some link>
+foo :: Int
+foo = 23
diff --git a/html-test/src/IgnoreExports.hs b/html-test/src/IgnoreExports.hs
new file mode 100644
index 00000000..0321ad02
--- /dev/null
+++ b/html-test/src/IgnoreExports.hs
@@ -0,0 +1,10 @@
+{-# OPTIONS_HADDOCK ignore-exports #-}
+module IgnoreExports (foo) where
+
+-- | documentation for foo
+foo :: Int
+foo = 23
+
+-- | documentation for bar
+bar :: Int
+bar = 23
diff --git a/html-test/src/ModuleWithWarning.hs b/html-test/src/ModuleWithWarning.hs
new file mode 100644
index 00000000..e64d9d7e
--- /dev/null
+++ b/html-test/src/ModuleWithWarning.hs
@@ -0,0 +1,5 @@
+-- | Documentation for "ModuleWithWarning".
+module ModuleWithWarning {-# WARNING "This is an unstable interface. Prefer functions from \"Prelude\" instead!" #-} where
+
+foo :: Int
+foo = 23
diff --git a/html-test/src/NamedDoc.hs b/html-test/src/NamedDoc.hs
new file mode 100644
index 00000000..7c04ba72
--- /dev/null
+++ b/html-test/src/NamedDoc.hs
@@ -0,0 +1,4 @@
+module NamedDoc where
+
+-- $foo bar
+
diff --git a/html-test/src/NoLayout.hs b/html-test/src/NoLayout.hs
new file mode 100644
index 00000000..19b38b1d
--- /dev/null
+++ b/html-test/src/NoLayout.hs
@@ -0,0 +1,12 @@
+
+-- Haddock comments are parsed as separate declarations so we
+-- need to insert a ';' when using them with explicit layout.
+-- This should probably be changed.
+
+module NoLayout where {
+ -- | the function 'g'
+ ;
+ g :: Int;
+ g = undefined
+ }
+
diff --git a/html-test/src/NonGreedy.hs b/html-test/src/NonGreedy.hs
new file mode 100644
index 00000000..f51b55f5
--- /dev/null
+++ b/html-test/src/NonGreedy.hs
@@ -0,0 +1,5 @@
+module NonGreedy where
+
+-- | <url1> <url2>
+f :: a
+f = undefined
diff --git a/html-test/src/Properties.hs b/html-test/src/Properties.hs
new file mode 100644
index 00000000..05930ece
--- /dev/null
+++ b/html-test/src/Properties.hs
@@ -0,0 +1,9 @@
+module Properties where
+
+-- | Fibonacci number of given 'Integer'.
+--
+-- prop> fib n <= fib (n + 1)
+fib :: Integer -> Integer
+fib 0 = 0
+fib 1 = 1
+fib n = fib (n - 1) + fib (n - 2)
diff --git a/html-test/src/PruneWithWarning.hs b/html-test/src/PruneWithWarning.hs
new file mode 100644
index 00000000..bfa55ea2
--- /dev/null
+++ b/html-test/src/PruneWithWarning.hs
@@ -0,0 +1,15 @@
+{-# OPTIONS_HADDOCK prune #-}
+-- |
+-- What is tested here:
+--
+-- * If a binding has a deprecation message but no documentation, it is pruned
+-- when @OPTIONS_HADDOCK prune@ is used.
+--
+module PruneWithWarning (foo, bar) where
+
+foo :: Int
+foo = 23
+{-# DEPRECATED foo "use bar instead" #-}
+
+bar :: Int
+bar = 42
diff --git a/html-test/src/QuasiExpr.hs b/html-test/src/QuasiExpr.hs
new file mode 100644
index 00000000..970759ba
--- /dev/null
+++ b/html-test/src/QuasiExpr.hs
@@ -0,0 +1,34 @@
+{-# LANGUAGE TemplateHaskell #-}
+
+-- Used by QuasiQuote. Example taken from the GHC documentation.
+module QuasiExpr where
+
+import Language.Haskell.TH
+import Language.Haskell.TH.Quote
+
+data Expr = IntExpr Integer
+ | AntiIntExpr String
+ | BinopExpr BinOp Expr Expr
+ | AntiExpr String
+ deriving Show
+
+data BinOp = AddOp
+ | SubOp
+ | MulOp
+ | DivOp
+ deriving Show
+
+eval :: Expr -> Integer
+eval (IntExpr n) = n
+eval (BinopExpr op x y) = (opToFun op) (eval x) (eval y)
+ where
+ opToFun AddOp = (+)
+ opToFun SubOp = (-)
+ opToFun MulOp = (*)
+ opToFun DivOp = div
+
+expr = QuasiQuoter parseExprExp undefined undefined undefined
+
+-- cheating...
+parseExprExp :: String -> Q Exp
+parseExprExp _ = [| BinopExpr AddOp (IntExpr 1) (IntExpr 2) |]
diff --git a/html-test/src/QuasiQuote.hs b/html-test/src/QuasiQuote.hs
new file mode 100644
index 00000000..06762cf9
--- /dev/null
+++ b/html-test/src/QuasiQuote.hs
@@ -0,0 +1,9 @@
+{-# LANGUAGE TemplateHaskell, QuasiQuotes #-}
+
+-- example taken from the GHC documentation
+module QuasiQuote where
+
+import QuasiExpr
+
+val :: Integer
+val = eval [expr|1 + 2|]
diff --git a/html-test/src/SpuriousSuperclassConstraints.hs b/html-test/src/SpuriousSuperclassConstraints.hs
new file mode 100644
index 00000000..d9e43e1c
--- /dev/null
+++ b/html-test/src/SpuriousSuperclassConstraints.hs
@@ -0,0 +1,30 @@
+{-# LANGUAGE EmptyDataDecls, KindSignatures #-}
+-- |
+-- What is tested here:
+--
+-- Due to a change in GHC 7.6.1 we had a bug that superclass contraints were
+-- included in the instances list. Edward K. repported it here:
+--
+-- <http://www.haskell.org/pipermail/haskell-cafe/2012-September/103600.html>
+--
+-- And here is the corresponding theard on glasgow-haskell-users:
+--
+-- <http://www.haskell.org/pipermail/glasgow-haskell-users/2012-September/022914.html>
+--
+-- It has been fixed in:
+--
+-- > 6ccf78e15a525282fef61bc4f58a279aa9c21771
+-- > Fix spurious superclass constraints bug.
+--
+module SpuriousSuperclassConstraints where
+
+import Control.Applicative
+
+data SomeType (f :: * -> *) a
+
+instance Functor (SomeType f) where
+ fmap = undefined
+
+instance Applicative f => Applicative (SomeType f) where
+ pure = undefined
+ (<*>) = undefined
diff --git a/html-test/src/TH.hs b/html-test/src/TH.hs
new file mode 100644
index 00000000..f8178bcb
--- /dev/null
+++ b/html-test/src/TH.hs
@@ -0,0 +1,8 @@
+{-# LANGUAGE TemplateHaskell #-}
+
+module TH where
+
+import Language.Haskell.TH
+
+decl :: Q [Dec]
+decl = [d| f x = x|]
diff --git a/html-test/src/TH2.hs b/html-test/src/TH2.hs
new file mode 100644
index 00000000..ea85e547
--- /dev/null
+++ b/html-test/src/TH2.hs
@@ -0,0 +1,7 @@
+{-# LANGUAGE TemplateHaskell #-}
+
+module TH2 where
+
+import TH
+
+$( decl )
diff --git a/html-test/src/Test.hs b/html-test/src/Test.hs
new file mode 100644
index 00000000..d352f029
--- /dev/null
+++ b/html-test/src/Test.hs
@@ -0,0 +1,422 @@
+-----------------------------------------------------------------------------
+-- |
+-- Module : Test
+-- Copyright : (c) Simon Marlow 2002
+-- License : BSD-style
+--
+-- Maintainer : libraries@haskell.org
+-- Stability : provisional
+-- Portability : portable
+--
+-- This module illustrates & tests most of the features of Haddock.
+-- Testing references from the description: 'T', 'f', 'g', 'Visible.visible'.
+--
+-----------------------------------------------------------------------------
+
+-- This is plain comment, ignored by Haddock.
+
+module Test (
+
+ -- Section headings are introduced with '-- *':
+ -- * Type declarations
+
+ -- Subsection headings are introduced with '-- **' and so on.
+ -- ** Data types
+ T(..), T2, T3(..), T4(..), T5(..), T6(..),
+ N1(..), N2(..), N3(..), N4, N5(..), N6(..), N7(..),
+
+ -- ** Records
+ R(..), R1(..),
+
+ -- | test that we can export record selectors on their own:
+ p, q, u,
+
+ -- * Class declarations
+ C(a,b), D(..), E, F(..),
+
+ -- | Test that we can export a class method on its own:
+ a,
+
+ -- * Function types
+ f, g,
+
+ -- * Auxiliary stuff
+
+ -- $aux1
+
+ -- $aux2
+
+ -- $aux3
+
+ -- $aux4
+
+ -- $aux5
+
+ -- $aux6
+
+ -- $aux7
+
+ -- $aux8
+
+ -- $aux9
+
+ -- $aux10
+
+ -- $aux11
+
+ -- $aux12
+
+ -- | This is some inline documentation in the export list
+ --
+ -- > a code block using bird-tracks
+ -- > each line must begin with > (which isn't significant unless it
+ -- > is at the beginning of the line).
+
+ -- * A hidden module
+ module Hidden,
+
+ -- * A visible module
+ module Visible,
+
+ {-| nested-style doc comments -}
+
+ -- * Existential \/ Universal types
+ Ex(..),
+
+ -- * Type signatures with argument docs
+ k, l, m, o,
+
+ -- * A section
+ -- and without an intervening comma:
+ -- ** A subsection
+
+{-|
+ > a literal line
+
+ $ a non /literal/ line $
+-}
+
+ f',
+
+ withType, withoutType
+ ) where
+
+import Hidden
+import Visible
+import Data.Maybe
+
+bla = Nothing
+
+-- | This comment applies to the /following/ declaration
+-- and it continues until the next non-comment line
+data T a b
+ = A Int (Maybe Float) -- ^ This comment describes the 'A' constructor
+ | -- | This comment describes the 'B' constructor
+ B (T a b, T Int Float) -- ^
+
+-- | An abstract data declaration
+data T2 a b = T2 a b
+
+-- | A data declaration with no documentation annotations on the constructors
+data T3 a b = A1 a | B1 b
+
+-- A data declaration with no documentation annotations at all
+data T4 a b = A2 a | B2 b
+
+-- A data declaration documentation on the constructors only
+data T5 a b
+ = A3 a -- ^ documents 'A3'
+ | B3 b -- ^ documents 'B3'
+
+-- | Testing alternative comment styles
+data T6
+ -- | This is the doc for 'A4'
+ = A4
+ | B4
+ | -- ^ This is the doc for 'B4'
+
+ -- | This is the doc for 'C4'
+ C4
+
+-- | A newtype
+newtype N1 a = N1 a
+
+-- | A newtype with a fieldname
+newtype N2 a b = N2 {n :: a b}
+
+-- | A newtype with a fieldname, documentation on the field
+newtype N3 a b = N3 {n3 :: a b -- ^ this is the 'n3' field
+ }
+
+-- | An abstract newtype - we show this one as data rather than newtype because
+-- the difference isn\'t visible to the programmer for an abstract type.
+newtype N4 a b = N4 a
+
+newtype N5 a b = N5 {n5 :: a b -- ^ no docs on the datatype or the constructor
+ }
+
+newtype N6 a b = N6 {n6 :: a b
+ }
+ -- ^ docs on the constructor only
+
+-- | docs on the newtype and the constructor
+newtype N7 a b = N7 {n7 :: a b
+ }
+ -- ^ The 'N7' constructor
+
+
+class (D a) => C a where
+ -- |this is a description of the 'a' method
+ a :: IO a
+ b :: [a]
+ -- ^ this is a description of the 'b' method
+ c :: a -- c is hidden in the export list
+
+-- ^ This comment applies to the /previous/ declaration (the 'C' class)
+
+class D a where
+ d :: T a b
+ e :: (a,a)
+-- ^ This is a class declaration with no separate docs for the methods
+
+instance D Int where
+ d = undefined
+ e = undefined
+
+-- instance with a qualified class name
+instance Test.D Float where
+ d = undefined
+ e = undefined
+
+class E a where
+ ee :: a
+-- ^ This is a class declaration with no methods (or no methods exported)
+
+-- This is a class declaration with no documentation at all
+class F a where
+ ff :: a
+
+-- | This is the documentation for the 'R' record, which has four fields,
+-- 'p', 'q', 'r', and 's'.
+data R =
+ -- | This is the 'C1' record constructor, with the following fields:
+ C1 { p :: Int -- ^ This comment applies to the 'p' field
+ , q :: forall a . a->a -- ^ This comment applies to the 'q' field
+ , -- | This comment applies to both 'r' and 's'
+ r,s :: Int
+ }
+ | C2 { t :: T1 -> (T2 Int Int)-> (T3 Bool Bool) -> (T4 Float Float) -> T5 () (),
+ u,v :: Int
+ }
+ -- ^ This is the 'C2' record constructor, also with some fields:
+
+-- | Testing different record commenting styles
+data R1
+ -- | This is the 'C3' record constructor
+ = C3 {
+ -- | The 's1' record selector
+ s1 :: Int
+ -- | The 's2' record selector
+ , s2 :: Int
+ , s3 :: Int -- NOTE: In the original examples/Test.hs in Haddock, there is an extra "," here.
+ -- Since GHC doesn't allow that, I have removed it in this file.
+ -- ^ The 's3' record selector
+ }
+
+-- These section headers are only used when there is no export list to
+-- give the structure of the documentation:
+
+-- * This is a section header (level 1)
+-- ** This is a section header (level 2)
+-- *** This is a section header (level 3)
+
+{-|
+In a comment string we can refer to identifiers in scope with
+single quotes like this: 'T', and we can refer to modules by
+using double quotes: "Foo". We can add emphasis /like this/.
+
+ * This is a bulleted list
+
+ - This is the next item (different kind of bullet)
+
+ (1) This is an ordered list
+
+ 2. This is the next item (different kind of bullet)
+
+ [cat] a small, furry, domesticated mammal
+
+ [pineapple] a fruit grown in the tropics
+
+@
+ This is a block of code, which can include other markup: 'R'
+ formatting
+ is
+ significant
+@
+
+> this is another block of code
+
+We can also include URLs in documentation: <http://www.haskell.org/>.
+-}
+
+f :: C a => a -> Int
+
+-- | we can export foreign declarations too
+foreign import ccall g :: Int -> IO CInt
+
+-- | this doc string has a parse error in it: \'
+h :: Int
+h = 42
+
+
+-- $aux1 This is some documentation that is attached to a name ($aux1)
+-- rather than a source declaration. The documentation may be
+-- referred to in the export list using its name.
+--
+-- @ code block in named doc @
+
+-- $aux2 This is some documentation that is attached to a name ($aux2)
+
+-- $aux3
+-- @ code block on its own in named doc @
+
+-- $aux4
+--
+-- @ code block on its own in named doc (after newline) @
+
+{- $aux5 a nested, named doc comment
+
+ with a paragraph,
+
+ @ and a code block @
+-}
+
+-- some tests for various arrangements of code blocks:
+
+{- $aux6
+>test
+>test1
+
+@ test2
+ test3
+@
+-}
+
+{- $aux7
+@
+test1
+test2
+@
+-}
+
+{- $aux8
+>test3
+>test4
+-}
+
+{- $aux9
+@
+test1
+test2
+@
+
+>test3
+>test4
+-}
+
+{- $aux10
+>test3
+>test4
+
+@
+test1
+test2
+@
+-}
+
+-- This one is currently wrong (Haddock 0.4). The @...@ part is
+-- interpreted as part of the bird-tracked code block.
+{- $aux11
+aux11:
+
+>test3
+>test4
+
+@
+test1
+test2
+@
+-}
+
+-- $aux12
+-- > foo
+--
+-- > bar
+--
+
+-- | A data-type using existential\/universal types
+data Ex a
+ = forall b . C b => Ex1 b
+ | forall b . Ex2 b
+ | forall b . C a => Ex3 b -- NOTE: I have added "forall b" here make GHC accept this file
+ | Ex4 (forall a . a -> a)
+
+-- | This is a function with documentation for each argument
+k :: T () () -- ^ This argument has type 'T'
+ -> (T2 Int Int) -- ^ This argument has type 'T2 Int Int'
+ -> (T3 Bool Bool -> T4 Float Float) -- ^ This argument has type @T3 Bool Bool -> T4 Float Float@
+ -> T5 () () -- ^ This argument has a very long description that should
+ -- hopefully cause some wrapping to happen when it is finally
+ -- rendered by Haddock in the generated HTML page.
+ -> IO () -- ^ This is the result type
+
+-- This function has arg docs but no docs for the function itself
+l :: (Int, Int, Float) -- ^ takes a triple
+ -> Int -- ^ returns an 'Int'
+
+-- | This function has some arg docs
+m :: R
+ -> N1 () -- ^ one of the arguments
+ -> IO Int -- ^ and the return value
+
+-- | This function has some arg docs but not a return value doc
+
+-- can't use the original name ('n') with GHC
+newn :: R -- ^ one of the arguments, an 'R'
+ -> N1 () -- ^ one of the arguments
+ -> IO Int
+newn = undefined
+
+
+-- | A foreign import with argument docs
+foreign import ccall unsafe
+ o :: Float -- ^ The input float
+ -> IO Float -- ^ The output float
+
+-- | We should be able to escape this: \#\#\#
+
+-- p :: Int
+-- can't use the above original definition with GHC
+newp :: Int
+newp = undefined
+
+-- | a function with a prime can be referred to as 'f''
+-- but f' doesn't get link'd 'f\''
+f' :: Int
+
+-- | Comment on a definition without type signature
+withoutType = undefined
+
+-- | Comment on a definition with type signature
+withType :: Int
+withType = 1
+
+-- Add some definitions here so that this file can be compiled with GHC
+
+data T1
+f = undefined
+f' = undefined
+type CInt = Int
+k = undefined
+l = undefined
+m = undefined
diff --git a/html-test/src/Ticket112.hs b/html-test/src/Ticket112.hs
new file mode 100644
index 00000000..c9cd5117
--- /dev/null
+++ b/html-test/src/Ticket112.hs
@@ -0,0 +1,9 @@
+{-# LANGUAGE MagicHash #-}
+
+module Ticket112 where
+
+import GHC.Prim
+
+-- | ...given a raw 'Addr#' to the string, and the length of the string.
+f :: a
+f = undefined
diff --git a/html-test/src/Ticket61.hs b/html-test/src/Ticket61.hs
new file mode 100644
index 00000000..26ca287f
--- /dev/null
+++ b/html-test/src/Ticket61.hs
@@ -0,0 +1,3 @@
+module Ticket61 (module Ticket61_Hidden) where
+
+import Ticket61_Hidden
diff --git a/html-test/src/Ticket61_Hidden.hs b/html-test/src/Ticket61_Hidden.hs
new file mode 100644
index 00000000..583c10cd
--- /dev/null
+++ b/html-test/src/Ticket61_Hidden.hs
@@ -0,0 +1,7 @@
+{-# OPTIONS_HADDOCK hide #-}
+
+module Ticket61_Hidden where
+
+class C a where
+ -- | A comment about f
+ f :: a
diff --git a/html-test/src/Ticket75.hs b/html-test/src/Ticket75.hs
new file mode 100644
index 00000000..94a2f115
--- /dev/null
+++ b/html-test/src/Ticket75.hs
@@ -0,0 +1,7 @@
+module Ticket75 where
+
+data a :- b = Q
+
+-- | A reference to ':-'
+f :: Int
+f = undefined
diff --git a/html-test/src/TypeFamilies.hs b/html-test/src/TypeFamilies.hs
new file mode 100644
index 00000000..561f95fd
--- /dev/null
+++ b/html-test/src/TypeFamilies.hs
@@ -0,0 +1,28 @@
+{-# LANGUAGE TypeFamilies #-}
+
+module TypeFamilies where
+
+-- | Type family G
+type family G a :: *
+
+-- | A class with an associated type
+class A a where
+ -- | An associated type
+ data B a :: * -> *
+ -- | A method
+ f :: B a Int
+
+-- | Doc for family
+type family F a
+
+
+-- | Doc for G Int
+type instance G Int = Bool
+type instance G Float = Int
+
+
+instance A Int where
+ data B Int x = Con x
+ f = Con 3
+
+g = Con 5
diff --git a/html-test/src/TypeOperators.hs b/html-test/src/TypeOperators.hs
new file mode 100644
index 00000000..edbb9344
--- /dev/null
+++ b/html-test/src/TypeOperators.hs
@@ -0,0 +1,20 @@
+{-# LANGUAGE TypeOperators #-}
+module TypeOperators (
+ -- * stuff
+ (:-:),
+ (:+:),
+ Op,
+ O(..),
+ biO,
+) where
+
+data a :-: b
+
+data (a :+: b) c
+
+data a `Op` b
+
+newtype (g `O` f) a = O { unO :: g (f a) }
+
+biO :: (g `O` f) a
+biO = undefined
diff --git a/html-test/src/Unicode.hs.disabled b/html-test/src/Unicode.hs.disabled
new file mode 100644
index 00000000..d5bbf445
--- /dev/null
+++ b/html-test/src/Unicode.hs.disabled
@@ -0,0 +1,6 @@
+module Unicode where
+
+-- | γλώσσα
+x :: Int
+x = 1
+
diff --git a/html-test/src/Visible.hs b/html-test/src/Visible.hs
new file mode 100644
index 00000000..cad71931
--- /dev/null
+++ b/html-test/src/Visible.hs
@@ -0,0 +1,3 @@
+module Visible where
+visible :: Int -> Int
+visible a = a