Re: GHC 7.10 regression when using foldr

2015-01-20 Thread Malcolm Wallace
On 20 Jan 2015, at 11:20, Björn Peemöller wrote: The reason is the usage of foldr, which changed its type from foldr :: (a - b - b) - b - [a] - b -- GHC 7.8.4 to foldr :: Foldable t = (a - b - b) - b - t a - b -- GHC 7.10.1 Thus, the use of foldr is now ambiguous. I can fix this by

Fwd: UNPACK Existential datatype

2015-01-20 Thread Nicholas Clarke
I'd like to be able to use the UNPACK pragma on an existentially quantified datatype. So as in the below example: {-# LANGUAGE ExistentialQuantification #-} data Foo = forall a. Show a = Foo !a instance Show Foo where show (Foo a) = Foo! ++ show a data Bar = Bar {-# UNPACK #-} !Foo

Re: GHC 7.10 regression when using foldr

2015-01-20 Thread Edward Kmett
There is a limited set of situations where the new signatures can fail to infer, where it would infer before. This can happen when you construct a Foldable/Traversable value using polymorphic tools (like Read) that were previously instantiated for list, but where since foldr et al. are now

GHC 7.10 regression when using foldr

2015-01-20 Thread Björn Peemöller
I just discovered that the following program compiled fine using GHC 7.8.4 but was rejected by GHC 7.10.1-rc1: ~~~ data List a = Nil | Cons a (List a) instance Read a = Read (List a) where readsPrec d s = map convert (readsPrec d s) where convert (xs, s2) = (foldr Cons Nil xs, s2) ~~~

Re: Fwd: UNPACK Existential datatype

2015-01-20 Thread Roman Cheplyaka
Interesting question. I managed to trace this to: compiler/basicTypes/MkId.hs:699 isUnpackableType fam_envs ty | Just (tc, _) - splitTyConApp_maybe ty , Just con - tyConSingleAlgDataCon_maybe tc , isVanillaDataCon con = ok_con_args (unitNameSet (getName tc)) con | otherwise = False

Re: GHC 7.10 regression when using foldr

2015-01-20 Thread Kim-Ee Yeoh
On Tue, Jan 20, 2015 at 6:45 PM, Edward Kmett ekm...@gmail.com wrote: I can at least say that the incident rate for cases seems to be very low, especially when it is contrasted against the pain users have had with using the existing Foldable/Traversable imports where virtually everything in

Re: ghc-7.10.0 type inference regression when faking injective type families

2015-01-20 Thread adam vogt
I've added it as https://ghc.haskell.org/trac/ghc/ticket/10009 On Tue, Jan 20, 2015 at 11:23 AM, Richard Eisenberg e...@cis.upenn.edu wrote: After quite a bit of thought, I agree that this is a regression and that the original program should be accepted. Make a bug report! Thanks, Richard

Re: ghc-7.10.0 type inference regression when faking injective type families

2015-01-20 Thread Richard Eisenberg
After quite a bit of thought, I agree that this is a regression and that the original program should be accepted. Make a bug report! Thanks, Richard ___ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org

Re: Thread behavior in 7.8.3

2015-01-20 Thread Michael Jones
Simon, This was fixed some time back. I combed the code base looking for other busy loops and there are no more. I commented out the code that runs the I2C + Machines + IO stuff, and only left the GUI code. It appears that just the wxhaskell part of the program fails to start. This matches a

Re: GHC 7.10 regression when using foldr

2015-01-20 Thread Edward Kmett
On Tue, Jan 20, 2015 at 9:00 AM, Kim-Ee Yeoh k...@atamo.com wrote: There are few reports because the change hasn't affected the dark majority yet. RC builds are used by a tiny fraction. There's a long tail of users still on 7.6, 7.4, 7.2, and 6.x. We've been actively testing since the

Found hole

2015-01-20 Thread Volker Wysk
Hello! What is a hole? This program fails to compile: main = _exit 0 I get this error message: ex.hs:1:8: Found hole ‘_exit’ with type: t Where: ‘t’ is a rigid type variable bound by the inferred type of main :: t at ex.hs:1:1 Relevant bindings include main :: t

Re: Found hole

2015-01-20 Thread Brandon Allbery
On Tue, Jan 20, 2015 at 1:36 PM, Volker Wysk vertei...@volker-wysk.de wrote: What is a hole? https://downloads.haskell.org/~ghc/latest/docs/html/users_guide/typed-holes.html When I replace _exit with foo, it produces a not in scope error, as expected. What is special about _exit? It doesn't

Re: Found hole

2015-01-20 Thread Edward Z. Yang
Hello Volker, All identifiers prefixed with an underscore are typed holes, see: https://downloads.haskell.org/~ghc/7.8.3/docs/html/users_guide/typed-holes.html Edward Excerpts from Volker Wysk's message of 2015-01-20 10:36:09 -0800: Hello! What is a hole? This program fails to compile:

Re: Found hole

2015-01-20 Thread htebalaka
They are described at these two links: https://www.haskell.org/haskellwiki/GHC/Typed_holes https://downloads.haskell.org/~ghc/7.8.1-rc1/docs/html/users_guide/typed-holes.html Essentially, identifiers that are not otherwise in scope and consist of an underscore or that have a trailing underscore

Re: Thread behavior in 7.8.3

2015-01-20 Thread Simon Marlow
My guess would be that either - a thread is in a non-allocating loop - a long-running foreign call is marked unsafe Either of these would block the other threads. ThreadScope together with some traceEventIO calls might help you identify the culprit. Cheers, Simon On 20/01/2015 15:49,

Re: Package version question with Cabal

2015-01-20 Thread Volker Wysk
Am Montag, 19. Januar 2015, 23:32:09 schrieben Sie: On Mon, Jan 19, 2015 at 11:14 PM, Volker Wysk vertei...@volker-wysk.de wrote: I've uploaded my library to Hackage, and now I'm trying to install it via cabal: At a guess, the index has not yet been updated --- you may need to wait some

Re: GHC 7.10 regression when using foldr

2015-01-20 Thread Edward Z. Yang
I like this proposal: if you're explicit about an import that would otherwise be implicit by Prelude, you shouldn't get a warning for it. If it is not already the case, we also need to make sure the implicit Prelude import never causes unused import errors. Edward Excerpts from Edward Kmett's

Re: GHC 7.10 regression when using foldr

2015-01-20 Thread Edward Kmett
I was assuming that the list was generated by doing more or less the same check we do now. I haven't looked at the code for it. If so, then it seems it wouldn't flag a now-unnecessary Data.Traversable dependency for instance. At least not without rather significant retooling. I might be off in

Re: GHC 7.10 regression when using foldr

2015-01-20 Thread Edward Kmett
It isn't without a cost. On the down-side, the results of -ddump-minimal-imports would be er.. less minimal. On Tue, Jan 20, 2015 at 6:47 PM, Edward Z. Yang ezy...@mit.edu wrote: I like this proposal: if you're explicit about an import that would otherwise be implicit by Prelude, you

Re: GHC 7.10 regression when using foldr

2015-01-20 Thread Bryan O'Sullivan
On Tue, Jan 20, 2015 at 3:02 PM, Herbert Valerio Riedel h...@gnu.org wrote: I'm a bit confused, several past attoparsec versions seem to build just fine with GHC 7.10: https://ghc.haskell.org/~hvr/buildreports/attoparsec.html were there hidden breakages not resulting in compile errors?

Re: Found hole

2015-01-20 Thread htebalaka
Unless it behaves differently in GHC than GHCi, you can still use underscore prefixed identifiers, provided they are in scope. I only get a type hole message if the identifier isn't defined anywhere else. let _x = 2 _x 2 _y Found hole '_y' with type: t ... -- View this message in context:

Re: GHC 7.10 regression when using foldr

2015-01-20 Thread Edward Kmett
Sure. Adding it to the CHANGELOG makes a lot of sense. I first found out about it only a few weeks ago when Herbert mentioned it in passing. Of course, the geek in me definitely prefers technical fixes to human ones. Humans are messy. =) I'd be curious how much of the current suite of warnings

Re: GHC 7.10 regression when using foldr

2015-01-20 Thread Herbert Valerio Riedel
Hello Bryan, On 2015-01-20 at 23:17:01 +0100, Bryan O'Sullivan wrote: [...] For the record, it took me almost an hour to update attoparsec to fix all the various regressions, or to put it more charitably changes, introduced in GHC 7.10. I have twenty-something other packages to go through. I

Re: GHC 7.10 regression when using foldr

2015-01-20 Thread Edward Z. Yang
I don't see why that would be the case: we haven't *excluded* any old import lists, so -ddump-minimal-imports could still take advantage of Prelude in a warning-free way. Edward Excerpts from Edward Kmett's message of 2015-01-20 16:36:53 -0800: It isn't without a cost. On the down-side, the

RE: ghc-7.10.0 type inference regression when faking injective type families

2015-01-20 Thread Simon Peyton Jones
Yes, I fixed it on the train. Most helpful. Busy tomorrow but I should have a fix committed by the end of the week Simon | -Original Message- | From: Glasgow-haskell-users [mailto:glasgow-haskell-users- | boun...@haskell.org] On Behalf Of Richard Eisenberg | Sent: 20 January 2015 16:24

Re: GHC 7.10 regression when using foldr

2015-01-20 Thread Edward Kmett
Building -Wall clean across this change-over has a big of a trick to it. The easiest way I know of when folks already had lots of import Data.Foldable import Data.Traversable stuff is to just add import Prelude explicitly to the bottom of your import list rather than painstakingly exclude

Re: Thread behavior in 7.8.3

2015-01-20 Thread Michael Jones
Simon, The code below hangs on the frameEx function. But, if I change it to: f - frameCreate objectNull idAny linti-scope PMBus Scope Tool rectZero (frameDefaultStyle .|. wxMAXIMIZE) it will progress, but no frame pops up, except once in many tries. Still hangs, but progresses

Re: Found hole

2015-01-20 Thread David Feuer
Just use exit_ or something instead. Typed holes are a *really useful* mechanism. On Tue, Jan 20, 2015 at 3:51 PM, migmit mig...@gmail.com wrote: DON'T DO THAT! Seriously, turn off compile-time type checking completely just to start an identifier with an underscore??? Отправлено с iPad 20

Re: Found hole

2015-01-20 Thread Edward Kmett
FWIW- you can think of a 'hole' as a not in scope error with a ton of useful information about the type such a term would have to have in order to go in the location you referenced it. This promotes a very useful style of type-driven development that is common in Agda, where you write out your

Re: Thread behavior in 7.8.3

2015-01-20 Thread Carter Schonwald
i think ben gamari hit similar/related issues with the lib usb bindings in 7.8, and i believe some / all of them are fixed in 7.10 (i could be mixing things up though) On Tue, Jan 20, 2015 at 10:43 PM, Michael Jones m...@proclivis.com wrote: Simon, The code below hangs on the frameEx

Re: GHC 7.10 regression when using foldr

2015-01-20 Thread Herbert Valerio Riedel
On 2015-01-21 at 00:27:39 +0100, Edward Z. Yang wrote: Hello Edward, Shouldn't we publicize this trick? Perhaps in the changelog? Fwiw, I've added that workaround/recipe to https://ghc.haskell.org/trac/ghc/wiki/Migration/7.10#GHCsaysTheimportof...isredundant feel free to improve the

[solved] Re: Found hole

2015-01-20 Thread Volker Wysk
Hello! I've found what went wrong: _exit wasn't in scope, so it was interpreted to be a typed hole. Thanks Volker ___ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

Re: Found hole

2015-01-20 Thread Alex Hammel
You can get typed holes to compile with a warning and a runtime error with the -fdefer-type-errors flag, if that's what you want. However, it's perfectly legal to use identifiers which look like typed holes. This works fine on 7.8.3ghc: _exit = print main = _exit 0 On Tue, Jan 20, 2015 at 11:25

Re: ghc-7.10.0 type inference regression when faking injective type families

2015-01-20 Thread David Feuer
Wrongly, as it turned out. Sorry! The problem remains. On Tue, Jan 20, 2015 at 2:37 PM, David Feuer david.fe...@gmail.com wrote: And I've closed it as worksforme. I couldn't reproduce the problem with 7.11.20150103. On Tue, Jan 20, 2015 at 11:42 AM, adam vogt vogt.a...@gmail.com wrote: I've

Re: Found hole

2015-01-20 Thread migmit
DON'T DO THAT! Seriously, turn off compile-time type checking completely just to start an identifier with an underscore??? Отправлено с iPad 20 янв. 2015 г., в 21:39, Alex Hammel ahamme...@gmail.com написал(а): You can get typed holes to compile with a warning and a runtime error with

Re: Found hole

2015-01-20 Thread Volker Wysk
Hi! Am Dienstag, 20. Januar 2015, 13:44:01 schrieben Sie: The leading underscore invokes the typed holes extension. If you want to use such names, you'll need {-# LANGUAGE NoTypedHoles #-} as the first line of the source file. I get this error, when I use {-# LANGUAGE NoTypedHoles #-}:

Re: ghc-7.10.0 type inference regression when faking injective type families

2015-01-20 Thread David Feuer
And I've closed it as worksforme. I couldn't reproduce the problem with 7.11.20150103. On Tue, Jan 20, 2015 at 11:42 AM, adam vogt vogt.a...@gmail.com wrote: I've added it as https://ghc.haskell.org/trac/ghc/ticket/10009 On Tue, Jan 20, 2015 at 11:23 AM, Richard Eisenberg e...@cis.upenn.edu

Re: Found hole

2015-01-20 Thread Alex Hammel
The only reference to a NoTypedHoles extension google can find is this thread. Odd. On Tue, Jan 20, 2015 at 11:22 AM, Volker Wysk vertei...@volker-wysk.de wrote: Hi! Am Dienstag, 20. Januar 2015, 13:44:01 schrieben Sie: The leading underscore invokes the typed holes extension. If you want