un-used record wildcards
Simon Peyton-Jones
simonpj at microsoft.com
Thu Oct 14 18:06:49 EDT 2010
Which version of GHC are you using? GHC 6.12 does not complain about unused variables bound by "..". Try this, which complains about y, but not g.
Simon
{-# LANGUAGE RecordWildCards #-}
module Test where
data T = MkT { f,g :: Int }
p (MkT { .. }) y = f
| -----Original Message-----
| From: glasgow-haskell-users-bounces at haskell.org [mailto:glasgow-haskell-users-
| bounces at haskell.org] On Behalf Of Serge D. Mechveliani
| Sent: 14 October 2010 11:01
| To: Antoine Latter
| Cc: glasgow-haskell-users at haskell.org
| Subject: Re: un-used record wildcards
|
| On Wed, Oct 13, 2010 at 01:47:11PM -0500, Antoine Latter wrote:
| > On Wed, Oct 13, 2010 at 1:02 PM, Serge D. Mechveliani <mechvel at botik.ru>
| wrote:
| > > Dear GHC developers,
| > >
| > > I use the language extension of RecordWildcards, for example,
| > > f (Foo {foo1 = n, foo2 = m, ..}) = ...
| > >
| > > But the complier warns about un-used values of foo3, foo4,
| > > probably, due to the extension of
| > > Foo {foo1 = n, foo2 = m, foo3 = foo3, foo4 = foo4}.
| > >
| > > In such cases, these warnings look as unneeded.
| > > Is it possible to have an un-used binding warnings with exception for
| > > wildcards in records?
| > > If not, then has it sense to introduce an option?
| > >
| >
| > If you're not using foo3 and foo4, can you not put it the ellipsis?
| > that won't cover every case (such as where you're using foo3 but not
| > foo4).
| >
| > Antoine
| >
|
| Indeed, thank you.
| It occurs that under RecordWildcards the compiler allows to skip some
| record fields in a pattern.
| _______________________________________________
| Glasgow-haskell-users mailing list
| Glasgow-haskell-users at haskell.org
| http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
More information about the Glasgow-haskell-users
mailing list