Navigation Menu

Skip to content

Commit

Permalink
Test Trac #5892
Browse files Browse the repository at this point in the history
  • Loading branch information
Simon Peyton Jones committed Mar 4, 2012
1 parent 24074aa commit 3adf208
Show file tree
Hide file tree
Showing 5 changed files with 39 additions and 0 deletions.
12 changes: 12 additions & 0 deletions tests/rename/should_fail/T5892a.hs
@@ -0,0 +1,12 @@
{-# LANGUAGE RecordWildCards #-}
{-# OPTIONS_GHC -Werror #-}

module T5892a where

import Data.Version ( Version( Version, versionBranch ))
-- Not importing its field: versionTags

foo :: Version -> Version
foo (Version {..}) -- Pattern match does not bind versionTags
= let versionBranch = []
in Version {..} -- Hence warning here
10 changes: 10 additions & 0 deletions tests/rename/should_fail/T5892a.stderr
@@ -0,0 +1,10 @@

T5892a.hs:12:8: Warning:
Fields of `Version' not initialised: Data.Version.versionTags
In the expression: Version {..}
In the expression: let versionBranch = [] in Version {..}
In an equation for `foo':
foo (Version {..}) = let versionBranch = [] in Version {..}

<no location info>:
Failing due to -Werror.
11 changes: 11 additions & 0 deletions tests/rename/should_fail/T5892b.hs
@@ -0,0 +1,11 @@
{-# LANGUAGE RecordWildCards #-}
module T5892b where

import Data.Version ( Version( Version, versionBranch ))
-- Not importing its field: versionTags

Version{..} = Version [] []
-- Binds versionBranch only

foo = T5892b.versionBranch
bar = T5892b.versionTags
4 changes: 4 additions & 0 deletions tests/rename/should_fail/T5892b.stderr
@@ -0,0 +1,4 @@

T5892b.hs:11:7:
Not in scope: `T5892b.versionTags'
Perhaps you meant `T5892b.versionBranch' (line 7)
2 changes: 2 additions & 0 deletions tests/rename/should_fail/all.T
Expand Up @@ -99,3 +99,5 @@ test('T5657', normal, compile_fail, [''])
test('T5745',
extra_clean(['T5745a.hi', 'T5745a.o', 'T5745b.hi', 'T5745b.o']),
multimod_compile_fail, ['T5745', '-v0'])
test('T5892a', normal, compile_fail, [''])
test('T5892b', normal, compile_fail, [''])

0 comments on commit 3adf208

Please sign in to comment.