aboutsummaryrefslogtreecommitdiff
path: root/examples/Test.hs
blob: 2ad444b1137f819f5c65755e6de49fda9db29434 (plain) (blame)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199
200
201
202
203
204
205
206
207
208
209
210
211
212
213
214
215
216
217
218
219
220
221
222
223
224
225
226
227
228
229
230
231
232
233
234
235
236
237
238
239
240
241
242
243
244
245
246
247
248
249
250
251
252
253
254
255
256
257
258
259
260
261
262
263
264
265
-----------------------------------------------------------------------------
-- |
-- 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(..),
	N1(..), N2(..), N3(..), N4, N5(..), N6(..), N7(..),

	-- ** Records
	R(..),

	-- | 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,

	-- $aux2
	-- * Auxiliary stuff

	-- $aux1

	-- $aux2

	-- $aux3

	-- $aux4

	-- $aux5

	-- | 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, n, o,
   ) where


-- | 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'

-- | A newtype
newtype N1 a b = N1 (a b)

-- | 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 :: Int
   b :: Float
   -- ^ this is a description of the 'b' method
   c :: Double -- 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

-- instance with a qualified class name
instance Test.D Float

class E a where
  ee :: Int
-- ^ 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 :: Float

-- | 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 -> T3 -> T4 -> T5,
       u,v :: Int
     }
  -- ^ This is the 'C2' record constructor, also with some fields:

-- 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)

@
     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 => Int -> 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 @
-}

-- | A data-type using existential\/universal types
data Ex a 
  = forall b . C b => Ex1 b
  | forall b . Ex2 b
  | C a => Ex3 b
  | Ex4 (forall a . a -> a)

-- | This is a function with documentation for each argument
k :: T 		-- ^ This argument has type 'T'
  -> T2 	-- ^ This argument has type 'T2'
  -> (T3 -> T4) -- ^ This argument has type @T3 -> T4@
  -> 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
n :: R		-- ^ one of the arguments, an 'R'
  -> N1		-- ^ one of the arguments
  -> IO Int

-- | A foreign import with argument docs
foreign import ccall unsafe 
 o :: Float  -- ^ The input float
   -> IO Float  -- ^ The output float