[Haskell-cafe] View patterns and warnings about overlapping or non-exhaustive patterns

Stephan Friedrichs deduktionstheorem at web.de
Wed Mar 11 12:22:19 EDT 2009


Hi,

I'm working on a data structure that uses Data.Sequence a lot, so views
are important and I tried to simplify my code using view patterns.

The problem is, that I keep getting warnings about both overlapping and
non-exhaustive pattern matches. A simple test case:

===============================T.hs===============================
{-# LANGUAGE ViewPatterns #-}

import Data.Sequence

test :: Seq a -> Seq b -> String
test (viewl -> EmptyL) (viewl -> EmptyL) = "empty, empty"
test (viewl -> EmptyL) (viewl -> _ :< _) = "empty, non-empty"
test (viewl -> _ :< _) (viewl -> EmptyL) = "non-empty, empty"
test _                 _                 = "non-empty, non-empty"
==================================================================

> ghci -Wall T.hs
GHCi, version 6.10.1: http://www.haskell.org/ghc/  :? for help
Loading package ghc-prim ... linking ... done.
Loading package integer ... linking ... done.
Loading package base ... linking ... done.
[1 of 1] Compiling Main             ( T.hs, interpreted )

T.hs:6:0:
    Warning: Pattern match(es) are overlapped
             In the definition of `test':
                 test ((viewl -> EmptyL)) ((viewl -> EmptyL)) = ...
                 test ((viewl -> EmptyL)) ((viewl -> _ :< _)) = ...
                 test ((viewl -> _ :< _)) ((viewl -> EmptyL)) = ...
                 test _ _ = ...

T.hs:6:0:
    Warning: Pattern match(es) are non-exhaustive
             In the definition of `test': Patterns not matched:
Ok, modules loaded: Main.

*Main> test empty (singleton 'a')
"empty, non-empty"
*Main> test (singleton 'b') (singleton 'a')
"non-empty, non-empty"
*Main> test (singleton 'b') empty
"non-empty, empty"
*Main> test empty empty
"empty, empty"

There are warnings about non-exhaustive and overlapping pattern matches,
but the tests show that this isn't the case. So what's the problem? I
don't want to turn off or ignore warnings.

//Stephan


-- 

Früher hieß es ja: Ich denke, also bin ich.
Heute weiß man: Es geht auch so.

 - Dieter Nuhr


More information about the Haskell-Cafe mailing list