Skip to content
Snippets Groups Projects
Commit 2a8867cf authored by Sebastian Graf's avatar Sebastian Graf Committed by Marge Bot
Browse files

Add a regression test for #11822

The particular test is already fixed, but the issue seems to have
multiple different test cases lumped together.
parent baf47661
No related branches found
No related tags found
No related merge requests found
{-# OPTIONS_GHC -Wincomplete-patterns -fforce-recomp #-}
{-# LANGUAGE OverloadedLists #-}
{-# LANGUAGE PatternSynonyms #-}
{-# LANGUAGE GeneralisedNewtypeDeriving #-}
module T11822 where
import Data.Sequence (Seq, pattern (:<|))
import Data.Set (Set)
newtype SiblingDependencies = SiblingDependencies Int
deriving (Eq, Ord, Enum, Integral, Real, Num)
newtype Depth = Depth Int
deriving (Eq, Ord, Enum, Integral, Real, Num)
data TreeNode prefix
= OnlyChild prefix
| LeafLast prefix
| LeafMid prefix
| NodeLast prefix
| NodeMid prefix
| PrefixedLast prefix (Seq SiblingDependencies) (Set prefix) Depth
| PrefixedMid prefix (Seq SiblingDependencies) (Set prefix) Depth
mkTreeNode
:: Ord prefix
=> prefix
-> Seq SiblingDependencies
-> Set prefix
-> Depth
-> TreeNode prefix
mkTreeNode t [] _ _ = OnlyChild t
mkTreeNode t [0] [] _ = LeafLast t
mkTreeNode t [_] [] _ = LeafMid t
mkTreeNode t [0] _ 0 = LeafLast t
mkTreeNode t [_] _ 0 = LeafMid t
mkTreeNode t [0] _ _ = NodeLast t
mkTreeNode t [_] _ _ = NodeMid t
mkTreeNode t (0 :<| ns) ds depth = PrefixedLast t ns ds depth
mkTreeNode t (_ :<| ns) ds depth = PrefixedMid t ns ds depth
T11822.hs:33:1: warning: [-Wincomplete-patterns (in -Wextra)]
Pattern match(es) are non-exhaustive
In an equation for ‘mkTreeNode’:
Patterns not matched:
_ (Data.Sequence.Internal.Seq _) _ _
_ (Data.Sequence.Internal.Seq _) _ p where p is not one of {0}
_ (Data.Sequence.Internal.Seq _) _ p where p is not one of {0}
_ (Data.Sequence.Internal.Seq _) _ p where p is not one of {0}
...
......@@ -40,16 +40,14 @@ test('T11303', normal, compile,
['-fwarn-incomplete-patterns -fwarn-overlapping-patterns +RTS -M1G -RTS'])
test('T11276', collect_compiler_stats('bytes allocated',10), compile,
['-fwarn-incomplete-patterns -fwarn-overlapping-patterns +RTS -M1G -RTS'])
test('T11303b', collect_compiler_stats('bytes allocated',10), compile,
['-fwarn-incomplete-patterns -fwarn-overlapping-patterns +RTS -M1G -RTS'])
test('T11374', collect_compiler_stats('bytes allocated',10), compile,
['-fwarn-incomplete-patterns -fwarn-overlapping-patterns +RTS -M1G -RTS'])
test('T11822', collect_compiler_stats('bytes allocated',10), compile,
['-fwarn-incomplete-patterns -fwarn-overlapping-patterns'])
test('T11195', collect_compiler_stats('bytes allocated',10), compile,
['-package ghc -fwarn-incomplete-patterns -fwarn-overlapping-patterns +RTS -M2G -RTS'])
test('T11984', normal, compile,
['-fwarn-incomplete-patterns -fwarn-overlapping-patterns'])
test('T14086', normal, compile,
......
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