Skip to content
Snippets Groups Projects
Commit d710fd66 authored by Vladislav Zavialov's avatar Vladislav Zavialov Committed by Marge Bot
Browse files

Testsuite: update some Haddock tests

Fixed tests:

* haddockA039: added to all.T
* haddockE004: replaced with T17561 (marked as expect_broken)

New tests:

* haddockA040: deriving clause for a data instance
* haddockA041: haddock and CPP #include
parent eb608235
No related branches found
No related tags found
No related merge requests found
Showing
with 60 additions and 8 deletions
-- | Comment on T
data T = MkT -- ^ Comment on MkT
-- | Comment on the first declaration
main = return ()
==================== Parser ====================
<document comment>
main = return ()
......@@ -49,7 +49,11 @@ test('haddockA038', normal, compile, ['-haddock -ddump-parsed'])
test('haddockA033', normal, compile, ['-haddock -ddump-parsed'])
test('haddockA034', normal, compile, ['-haddock -ddump-parsed'])
test('haddockA039', normal, compile, ['-haddock -ddump-parsed'])
test('haddockA040', normal, compile, ['-haddock -ddump-parsed'])
test('haddockA041', [extra_files(['IncludeMe.hs'])], compile, ['-haddock -ddump-parsed'])
test('T10398', normal, compile, ['-haddock -ddump-parsed'])
test('T11768', normal, compile, ['-haddock -ddump-parsed'])
test('T15206', normal, compile, ['-haddock -ddump-parsed'])
test('T16585', normal, compile, ['-haddock -ddump-parsed'])
test('T17561', expect_broken(17561), compile, ['-haddock -ddump-parsed'])
==================== Parser ====================
module CommentsBeforeArguments where
data A = A
data B = B
f1 ::
() Comment before -> () Comment after -> () Result after
() " Comment before "
-> () " Comment after " -> () " Result after "
f1 _ _ = ()
f2 ::
() Comment before -> () Comment after -> () Result after
() " Comment before "
-> () " Comment after " -> () " Result after "
f2 _ _ = ()
{-# LANGUAGE TypeFamilies #-}
module CommentsDataInstanceDeriving where
-- | Comment on the U data family
data family U a
-- | Comment on the U () data instance
data instance U () = UUnit
deriving ( Eq -- ^ Comment on the derived Eq (U ()) instance
, Ord -- ^ Comment on the derived Ord (U ()) instance
, Show -- ^ Comment on the derived Show (U ()) instance
)
==================== Parser ====================
module CommentsDataInstanceDeriving where
<document comment>
data family U a
<document comment>
data instance U ()
= UUnit
deriving (Eq " Comment on the derived Eq (U ()) instance",
Ord " Comment on the derived Ord (U ()) instance",
Show " Comment on the derived Show (U ()) instance")
{-# LANGUAGE CPP #-}
-- | Module header documentation
module Comments_and_CPP_include where
#include "IncludeMe.hs"
==================== Parser ====================
" Module header documentation"
module Comments_and_CPP_include where
<document comment>
data T = " Comment on MkT" MkT
#test('haddockE001', normal, compile_fail, ['-haddock'])
#test('haddockE002', normal, compile_fail, ['-haddock'])
#test('haddockE003', normal, compile_fail, ['-haddock'])
test('haddockE004', normal, compile_fail, ['-haddock'])
-- | awlkdajsads
main=undefined
haddockE004.hs:3:1: parse error on input ‘main’
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment