Warnings with OverloadedLists

Hello, I've bumped into strange GHC behaviour with OverloadedLists and pattern matching. Consider this example: {-# LANGUAGE OverloadedLists #-} len :: [a] -> Int len [] = 0 len (_:t) = 1 + len t If I load this with "ghci -Wall", I get a warning: Test.hs:4:1: Warning: Pattern match(es) are non-exhaustive In an equation for ‘len’: Patterns not matched: [] If I disable OverloadedLists extension, warning goes away. Can someone clear this behaviour out for me? It looks like a bug, but I'm not sure. Thanks for help, Nikolay.

Hi Nikolay,
On 16 June 2014 18:19, Nikolay Amiantov
If I disable OverloadedLists extension, warning goes away. Can someone clear this behaviour out for me? It looks like a bug, but I'm not sure.
I am not sure if this is a bug or not, but this page seems to explain the desugaring of patterns with OverloadedLists: https://ghc.haskell.org/trac/ghc/wiki/OverloadedLists As a workaround, you could try calling `toList` explicitly in a case statement to implement a `len` function for types with an IsList instance. Maybe something like the following. len :: IsList l => l -> Int len xs = case toList xs of [] -> ... Or even: len :: IsList l => l -> Int len = length . toList Hope this helps. -- Ozgur Akgun

Hi Ozgur,
On Wed, Jun 18, 2014 at 1:46 AM, Ozgur Akgun
I am not sure if this is a bug or not, but this page seems to explain the desugaring of patterns with OverloadedLists: https://ghc.haskell.org/trac/ghc/wiki/OverloadedLists
Thanks for the link, I've experimented a bit with this: 1) GHC will alert me if I use VIewPatterns and don't match _: len (id -> []) = 0 len (id -> (_:xs)) = 1 + len xs Warning: Pattern match(es) are non-exhaustive In an equation for ‘len’: Patterns not matched: _ I suppose this is because GHC cannot detect if "id" will yield bottom. 2) GHC, however, will alert me that I should also match [] if I use OverloadedLists, as shown before. If I have correctly understood this desugaring, it should warn me about matching _ as before. I can't quite understand behaviour (2) there. Any ideas? Nikolay.
participants (2)
-
Nikolay Amiantov
-
Ozgur Akgun