RE: match_co: needs more cases

2013-05-28 Thread Simon Peyton-Jones
It's harmless. But it's there to tell us that a RULE is not going to match 
because the LHS involves a coercion that is not Refl or a variable.   Matching 
on more complex coercions is likely to be fragile, since they can take a 
variety of forms.

So don't worry too much, but I'd be interested in a repro case

Simon

| -Original Message-
| From: glasgow-haskell-users-boun...@haskell.org [mailto:glasgow-haskell-
| users-boun...@haskell.org] On Behalf Of Evan Laforge
| Sent: 27 May 2013 18:56
| To: GHC users
| Subject: match_co: needs more cases
| 
| I made some strictifying changes and started getting this msg from ghc:
| 
| match_co: needs more cases
| vector-0.10.0.1:Data.Vector.Generic.Mutable.MVector{tc r46}
|   (Sym (vector-0.10.0.1:Data.Vector.TFCo:R:MutableVector{tc r45}))
|   main:Util.TimeVectorStorable.Sample{tc r4e} y{tv a4lK} [tv]
| 
| It's not just TimeVectorStorable.Sample (which is indeed stored in
| Data.Vectors), we also have some mysterious compiler-generated
| symbols:
| 
| match_co: needs more cases
| vector-0.10.0.1:Data.Vector.Generic.Mutable.MVector{tc rQA}
|   (Sym (vector-0.10.0.1:Data.Vector.TFCo:R:MutableVector{tc rQz}))
|   a{tv a6IH} [tv]
| 
| I assume this is harmless, but I didn't see any other references to
| this error on the web or on the ghc trac so maybe it's new?
| 
| ___
| Glasgow-haskell-users mailing list
| Glasgow-haskell-users@haskell.org
| http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: A language extension for dealing with Prelude.foldr vs Foldable.foldr and similar dilemmas

2013-05-28 Thread Chris Smith
+1

While it might work for teaching, it's not reasonable to ask software
developers who want to write useful software to depend on haskell98
instead of base if they want more relevant types.

I'd go one step further and say that we're not just talking about
whether someone is an advanced user either.  I'm probably among the
more advanced of Haskell users, but I'd still rather see specialized
type signatures in cases where one specific instance is far more
common than the others.  Yes, I know that certain combinators like
(***) and () are useful for functions, for example.  It still makes
me less productive to have those things stuffed off in a corner where
they are difficult to get to, and described in needlessly abstract
language.

I honestly can't understand the viewpoint that says that having the
compiler choose the unique most general type for imported symbols (or
give an error if none exists) is too complicated, yet programmers
manually substituting common instances into type signatures is no big
deal.  The first is fairly obvious work done by the compiler, which
the second needs programmers (yes, even experienced ones) to
occasionally get out a pencil and paper to work out the details.

On Tue, May 28, 2013 at 1:23 AM, Daniel Gorín dgo...@dc.uba.ar wrote:
 It is not only a matter of teaching, I think. After first learning the very 
 basics of a language, browsing the libraries that come included is a more or 
 less standard way of getting more acquainted with it. By including only the 
 abstract versions we are making it much harder to learn the common idioms.

 For instance, at the moment, how likely is that someone will start using 
 (), (***), (+++) or any of the useful combinators in Control.Arrow from 
 reading its haddock? These are very handy functions, easy to understand when 
 specialized to (-), but are usually reserved for advanced users since they 
 are presented only in their most general way. With an extension like this one 
 available, one could propose including specialized versions of them in 
 Data.Function and/or Data.Tuple/Data.Either; today it would be a very bad 
 idea due to the clash with Control.Arrow!

 Daniel

 On May 28, 2013, at 3:27 AM, Edward A Kmett wrote:

 This is basically what you get by default already with the raw proposal 
 we've been talking about -- the Preludes in the haskell98 and haskell2010 
 remain unmodified by this proposal and are available for teaching use.

 Sent from my iPhone

 On May 27, 2013, at 8:53 PM, Andrew Farmer afar...@ittc.ku.edu wrote:

 I generally agree with Iavor's points, but if this is such an issue, why 
 not make Prelude more general by default and have a special 'Prelude.Basic' 
 with the more specific type signatures for beginners? The general Prelude 
 would be implicitly imported as now, unless the module imported 
 Prelude.Basic unqualified. Then make Hackage warn/reject packages that use 
 Prelude.Basic.

 Tutorials/Books would have to tell readers to add a magic import 
 Prelude.Basic at the beginning of their source files, but tutorials for 
 other languages do this (public static void main(..)?) to relatively little 
 complaint.

 Sorry, I'm sure this has been proposed before... but the proposed extension 
 seems complicated to avoid some qualified imports/hidings. If we really 
 want people to use Foldable's foldr by default, then make it the default 
 and let beginners add a magic line once per file to get simpler types.

 Andrew


 On Mon, May 27, 2013 at 5:07 PM, Daniel Gorín dgo...@dc.uba.ar wrote:
 Hi Iavor,

 On May 27, 2013, at 6:18 PM, Iavor Diatchki wrote:

  Hello,
 
 
  On Fri, May 24, 2013 at 12:42 AM, Daniel Gorín dgo...@dc.uba.ar wrote:
  On May 24, 2013, at 9:28 AM, Simon Peyton-Jones wrote:
 
   How about (in Haskell98)
  
 module Data.List ( foldr, ...)
 import qualified Data.Foldable
 foldr :: (a - b - b) - b - [a] - b
 foldr = Data.Foldable.foldr
 
  It would not be the same! Using your example one will get that the 
  following fails to compile:
 
   import Data.List
   import Data.Foldable
   f = foldr
 
  The problem is that Data.List.foldr and Data.Foldable.foldr are here 
  different symbols with the same name.
  This is precisely why Foldable, Traversable, Category, etc are awkward 
  to use. The proposal is to make Data.List reexport Data.Foldable.foldr 
  (with a more specialized type) so that the module above can be accepted.
 
 
  I think that it is perfectly reasonable for this to fail to compile---to 
  me, this sort of implicit shadowing based on what extensions are turned 
  on would be very confusing.  It may seem obvious with a well-known 
  example, such as `foldr`, but I can easily imagine getting a headache 
  trying to figure out a new library that makes uses the proposed feature 
  in anger :)

 I understand your concern, but I don't quite see how a library could abuse 
 this feature. I mean, a library could export the same symbol with different