From nikita at karetnikov.org Mon Jun 1 16:40:55 2015 From: nikita at karetnikov.org (Nikita Karetnikov) Date: Mon, 01 Jun 2015 19:40:55 +0300 Subject: Arithmetic overflow in rem and mod Message-ID: <87pp5ffkko.fsf@karetnikov.org> According to the documentation, rem and mod must satisfy the following laws: -- > (x `quot` y)*y + (x `rem` y) == x rem -- > (x `div` y)*y + (x `mod` y) == x mod https://hackage.haskell.org/package/base-4.8.0.0/docs/src/GHC-Real.html Note, however, that there is a case when quot and div result in an arithmetic overflow: Prelude> (minBound :: Int) `quot` (-1) *** Exception: arithmetic overflow Prelude> (minBound :: Int) `div` (-1) *** Exception: arithmetic overflow while rem and mod don't: Prelude> (minBound :: Int) `rem` (-1) 0 Prelude> (minBound :: Int) `mod` (-1) 0 Is this a mistake? For the record, I'm aware of the safeint package, which raises the error for rem and mod, and this ticket: https://ghc.haskell.org/trac/ghc/ticket/8695 From david.feuer at gmail.com Mon Jun 1 17:23:55 2015 From: david.feuer at gmail.com (David Feuer) Date: Mon, 1 Jun 2015 13:23:55 -0400 Subject: Arithmetic overflow in rem and mod In-Reply-To: <87pp5ffkko.fsf@karetnikov.org> References: <87pp5ffkko.fsf@karetnikov.org> Message-ID: I think this is a mistake, yes. They should not raise such exceptions, but rather just wrap around?minBound `quot` (-1) should be -minBound=minBound. That would justify the behavior of rem and mod, and makes much more sense than the current behavior for Int as a ring. On Jun 1, 2015 12:41 PM, "Nikita Karetnikov" wrote: > According to the documentation, rem and mod must satisfy the following > laws: > > -- > (x `quot` y)*y + (x `rem` y) == x > rem > > -- > (x `div` y)*y + (x `mod` y) == x > mod > > https://hackage.haskell.org/package/base-4.8.0.0/docs/src/GHC-Real.html > > Note, however, that there is a case when quot and div result in an > arithmetic overflow: > > Prelude> (minBound :: Int) `quot` (-1) > *** Exception: arithmetic overflow > Prelude> (minBound :: Int) `div` (-1) > *** Exception: arithmetic overflow > > while rem and mod don't: > > Prelude> (minBound :: Int) `rem` (-1) > 0 > Prelude> (minBound :: Int) `mod` (-1) > 0 > > Is this a mistake? > > For the record, I'm aware of the safeint package, which raises the error > for rem and mod, and this ticket: > > https://ghc.haskell.org/trac/ghc/ticket/8695 > _______________________________________________ > Glasgow-haskell-users mailing list > Glasgow-haskell-users at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/glasgow-haskell-users > -------------- next part -------------- An HTML attachment was scrubbed... URL: From byron.hale at einfo.com Tue Jun 2 00:17:51 2015 From: byron.hale at einfo.com (Byron Hale) Date: Mon, 01 Jun 2015 17:17:51 -0700 Subject: ANN: Bayhac 2015 June 12, 13, 14 in Mountain View, CAANN: Message-ID: <556CF62F.8090900@einfo.com> Bayhac 2015 will be held June 12, 13, 14 at Hackers Dojo in Mountain View, CA. See http://bayhac.org/ to register. Light rail service is available from Caltrain to near Hackers Dojo. In addition, there can be shuttle service from Caltrain first thing in the morning and in the evening. Some known speakers are: Conal Elliott, Phil Freeman, Greg Weber, and Dan Burton You! If you would like to give a talk, send an email to bayhac2015-admin at googlegroups.com with the title and a brief explanation of what the talk will be on. It can be on anything Haskell related! We are also looking out for people who might be interested in conducting a more hands-on workshop. Twitter: https://twitter.com/bayhac2015 Byron Hale byron.hale at einfo.com @Hale_ByronL From rwbarton at gmail.com Tue Jun 2 15:51:22 2015 From: rwbarton at gmail.com (Reid Barton) Date: Tue, 2 Jun 2015 11:51:22 -0400 Subject: Arithmetic overflow in rem and mod In-Reply-To: References: <87pp5ffkko.fsf@karetnikov.org> Message-ID: The current behavior is quite intentional. On Mon, Jun 1, 2015 at 1:23 PM, David Feuer wrote: > I think this is a mistake, yes. They should not raise such exceptions, but > rather just wrap around?minBound `quot` (-1) should be -minBound=minBound. > That would justify the behavior of rem and mod, and makes much more sense > than the current behavior for Int as a ring. > Well, div has no relation to any ring operation of Int at all. It relies on a particular choice of representatives for the equivalence classes that the members of Int-as-a-ring are, and the ring operations do not depend on the choice of representatives. For example Int and Word are isomorphic as rings, but have different div operations when identified under this isomorphism. On Jun 1, 2015 12:41 PM, "Nikita Karetnikov" wrote: > >> According to the documentation, rem and mod must satisfy the following >> laws: >> >> -- > (x `quot` y)*y + (x `rem` y) == x >> rem >> >> -- > (x `div` y)*y + (x `mod` y) == x >> mod >> > The real law that defines the behavior of `div` on Int, though, is (the uglier to write in Haskell) toInteger (x `div` y) * toInteger y + toInteger (x `mod` y) == toInteger x together with the conditions that x `mod` y has the same sign as y and |x `mod` y| < |y| (here again |n| = abs (toInteger n)). With the condition that (x `div` y) * y + (x `mod` y) == x interpreted only as an equality of Ints, that is, as an equality mod (say) 2^64, there's no reason why we couldn't have for example 1 `mod` 3 = 0, 1 `div` 3 = 12297829382473034411 -- (2*2^64+1)/3 so the equality of Integers is really needed. When x = minBound :: Int and y = -1, the integers that would satisfy the div/mod law are -x and 0. I'm not sure whether you are intending to suggest that x `div` y be defined (as minBound :: Int), or that x `mod` y raise an exception. But given we should have toInteger (x `div` y) = -toInteger (minBound :: Int), toInteger (x `mod` y) = 0, setting x `div` y = _|_, x `mod` y = 0 is the most sensible definition. If the objection is that since x `div` y is _|_, then so too should be x `mod` y, because of the law (x `div` y)*y + (x `mod` y) == x, I don't think that follows. After all the law is already violated as written when y = 0 since x `div` 0 and x `mod` 0 are both _|_, so the equation takes the form _|_ + _|_ == x. I don't think it is a worse violation of the law to have _|_ + 0 == x when x = minBound and y = -1. Regards, Reid Barton -------------- next part -------------- An HTML attachment was scrubbed... URL: From ekmett at gmail.com Tue Jun 2 16:06:03 2015 From: ekmett at gmail.com (Edward Kmett) Date: Tue, 2 Jun 2015 18:06:03 +0200 Subject: Arithmetic overflow in rem and mod In-Reply-To: <87pp5ffkko.fsf@karetnikov.org> References: <87pp5ffkko.fsf@karetnikov.org> Message-ID: We went round and round on this back in August. The ultimate decision was to leave the existing behavior for quot and div as sufficient consensus for changing it was not reached. I've updated the ticket in question to reflect that resolution. -Edward On Mon, Jun 1, 2015 at 6:40 PM, Nikita Karetnikov wrote: > According to the documentation, rem and mod must satisfy the following > laws: > > -- > (x `quot` y)*y + (x `rem` y) == x > rem > > -- > (x `div` y)*y + (x `mod` y) == x > mod > > https://hackage.haskell.org/package/base-4.8.0.0/docs/src/GHC-Real.html > > Note, however, that there is a case when quot and div result in an > arithmetic overflow: > > Prelude> (minBound :: Int) `quot` (-1) > *** Exception: arithmetic overflow > Prelude> (minBound :: Int) `div` (-1) > *** Exception: arithmetic overflow > > while rem and mod don't: > > Prelude> (minBound :: Int) `rem` (-1) > 0 > Prelude> (minBound :: Int) `mod` (-1) > 0 > > Is this a mistake? > > For the record, I'm aware of the safeint package, which raises the error > for rem and mod, and this ticket: > > https://ghc.haskell.org/trac/ghc/ticket/8695 > _______________________________________________ > Glasgow-haskell-users mailing list > Glasgow-haskell-users at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/glasgow-haskell-users > -------------- next part -------------- An HTML attachment was scrubbed... URL: From g9ks157k at acme.softbase.org Tue Jun 2 16:28:18 2015 From: g9ks157k at acme.softbase.org (Wolfgang Jeltsch) Date: Tue, 02 Jun 2015 19:28:18 +0300 Subject: Ambiguity check and type families Message-ID: <1433262498.7963.19.camel@idefix> Hi, the following (contrived) code is accepted by GHC 7.8.3, but not 7.10.1: > {-# LANGUAGE TypeFamilies #-} > > type family F a :: * > > type family G b :: * > > x :: G (F a) ~ a => F a > x = undefined GHC 7.10.1 reports: > Could not deduce (F a0 ~ F a) > from the context (G (F a) ~ a) > bound by the type signature for x :: (G (F a) ~ a) => F a > at Test.hs:7:6-23 > NB: ?F? is a type function, and may not be injective > The type variable ?a0? is ambiguous > In the ambiguity check for the type signature for ?x?: > x :: forall a. (G (F a) ~ a) => F a > To defer the ambiguity check to use sites, enable AllowAmbiguousTypes > In the type signature for ?x?: x :: G (F a) ~ a => F a At a first look, this complaint seems reasonable, and I have already wondered why GHC 7.8.3 actually accepts the above code. >From an intuitive standpoint, however, the code seems actually acceptable to me. While it is true that type families are generally not injective, it is possible to derive the type a from F a by applying G. It would great if this code would be accepted by GHC again and if there was a workaround to make it work with GHC 7.10.1. At the moment, this change in the type checker from 7.8.3 to 7.10.1 breaks the incremental-computing package in a rather fundamental way. All the best, Wolfgang From iavor.diatchki at gmail.com Tue Jun 2 16:57:29 2015 From: iavor.diatchki at gmail.com (Iavor Diatchki) Date: Tue, 2 Jun 2015 09:57:29 -0700 Subject: Ambiguity check and type families In-Reply-To: <1433262498.7963.19.camel@idefix> References: <1433262498.7963.19.camel@idefix> Message-ID: Hi, that's an interesting example. To me this looks like a bug in GHC, although the issue is certainly a bit subtle. The reason I think it is a bug is that, if we name all the type functions in the signature and apply improvements using the fact that we are working with functions, then we get: x :: (F a ~ b, G b ~ a) => b x = undefined Now, this should be equivalent, and it is quite clear that there is no ambiguity here, as the `b` determines the `a` via the `G`. Interestingly, GHC accepts the program in this form. Also, if you ask it for the type of `x` using `:t` (which means instantiate the type and the generalize it again), we get another equivalent formulation: `x :: (F (G b) ~ b) => b`, which is also accepted by GHC. -Iavor On Tue, Jun 2, 2015 at 9:28 AM, Wolfgang Jeltsch wrote: > Hi, > > the following (contrived) code is accepted by GHC 7.8.3, but not 7.10.1: > > > {-# LANGUAGE TypeFamilies #-} > > > > type family F a :: * > > > > type family G b :: * > > > > x :: G (F a) ~ a => F a > > x = undefined > > GHC 7.10.1 reports: > > > Could not deduce (F a0 ~ F a) > > from the context (G (F a) ~ a) > > bound by the type signature for x :: (G (F a) ~ a) => F a > > at Test.hs:7:6-23 > > NB: ?F? is a type function, and may not be injective > > The type variable ?a0? is ambiguous > > In the ambiguity check for the type signature for ?x?: > > x :: forall a. (G (F a) ~ a) => F a > > To defer the ambiguity check to use sites, enable AllowAmbiguousTypes > > In the type signature for ?x?: x :: G (F a) ~ a => F a > > At a first look, this complaint seems reasonable, and I have already > wondered why GHC 7.8.3 actually accepts the above code. > > From an intuitive standpoint, however, the code seems actually > acceptable to me. While it is true that type families are generally not > injective, it is possible to derive the type a from F a by applying G. > > It would great if this code would be accepted by GHC again and if there > was a workaround to make it work with GHC 7.10.1. At the moment, this > change in the type checker from 7.8.3 to 7.10.1 breaks the > incremental-computing package in a rather fundamental way. > > All the best, > Wolfgang > > _______________________________________________ > Glasgow-haskell-users mailing list > Glasgow-haskell-users at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/glasgow-haskell-users > -------------- next part -------------- An HTML attachment was scrubbed... URL: From vogt.adam at gmail.com Tue Jun 2 17:00:27 2015 From: vogt.adam at gmail.com (adam vogt) Date: Tue, 2 Jun 2015 13:00:27 -0400 Subject: Ambiguity check and type families In-Reply-To: <1433262498.7963.19.camel@idefix> References: <1433262498.7963.19.camel@idefix> Message-ID: Hi Wolfgang, https://ghc.haskell.org/trac/ghc/ticket/10009 might be the same regression (fixed in HEAD) Regards, Adam On Tue, Jun 2, 2015 at 12:28 PM, Wolfgang Jeltsch < g9ks157k at acme.softbase.org> wrote: > Hi, > > the following (contrived) code is accepted by GHC 7.8.3, but not 7.10.1: > > > {-# LANGUAGE TypeFamilies #-} > > > > type family F a :: * > > > > type family G b :: * > > > > x :: G (F a) ~ a => F a > > x = undefined > > GHC 7.10.1 reports: > > > Could not deduce (F a0 ~ F a) > > from the context (G (F a) ~ a) > > bound by the type signature for x :: (G (F a) ~ a) => F a > > at Test.hs:7:6-23 > > NB: ?F? is a type function, and may not be injective > > The type variable ?a0? is ambiguous > > In the ambiguity check for the type signature for ?x?: > > x :: forall a. (G (F a) ~ a) => F a > > To defer the ambiguity check to use sites, enable AllowAmbiguousTypes > > In the type signature for ?x?: x :: G (F a) ~ a => F a > > At a first look, this complaint seems reasonable, and I have already > wondered why GHC 7.8.3 actually accepts the above code. > > From an intuitive standpoint, however, the code seems actually > acceptable to me. While it is true that type families are generally not > injective, it is possible to derive the type a from F a by applying G. > > It would great if this code would be accepted by GHC again and if there > was a workaround to make it work with GHC 7.10.1. At the moment, this > change in the type checker from 7.8.3 to 7.10.1 breaks the > incremental-computing package in a rather fundamental way. > > All the best, > Wolfgang > > _______________________________________________ > Glasgow-haskell-users mailing list > Glasgow-haskell-users at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/glasgow-haskell-users > -------------- next part -------------- An HTML attachment was scrubbed... URL: From austin at well-typed.com Tue Jun 2 21:31:04 2015 From: austin at well-typed.com (Austin Seipp) Date: Tue, 2 Jun 2015 16:31:04 -0500 Subject: HEADS UP: Final call for 7.10.2 is soon Message-ID: Hi *, I've just finished merging all the latest patches for GHC 7.10.2 into the STABLE branch. All in all, we've fixed a lot of bugs (over 80 tickets closed)! So, we'll probably be doing a 7.10.2 release here in a few weeks. The tentative plan was around the 14th, although it's not set in stone. (At worst, it would be pushed from the 14th to the 21st). With that in mind, if I could quickly direct your attention to the GHC bug tracker and the status page[1] - it would be really helpful if you check if the things you want are fixed! Specifically, if you want something fixed for the 7.10.2 release: - Make sure there is a ticket. It really needs to exist or we'll just forget! - If your bug is critical, please explain why! We really want to kill showstoppers ASAP, because bugs are much cheaper to fix early. If that's the case we can bump the priority if it's necessary to make things clear. - Set the milestone to 7.10.2. It'll automatically appear on the status page. That should be it - we'll be monitoring the status page regularly to keep track of new things. The current bug list is pretty small - we may move some of them out, or fix several more. So just try to let us know. As a sidenote, I'm quite happy with this release - it's fixed dozens of tricky bugs, improved some nasty corner cases in compiler performance, and overall seems like it will be high quality. Thanks to everyone who submitted patches! I'll send out another email next week as another reminder. [1] https://ghc.haskell.org/trac/ghc/wiki/Status/GHC-7.10.2 -- Regards, Austin Seipp, Haskell Consultant Well-Typed LLP, http://www.well-typed.com/ From g9ks157k at acme.softbase.org Tue Jun 2 21:58:49 2015 From: g9ks157k at acme.softbase.org (Wolfgang Jeltsch) Date: Wed, 03 Jun 2015 00:58:49 +0300 Subject: Ambiguity check and type families In-Reply-To: References: <1433262498.7963.19.camel@idefix> Message-ID: <1433282329.7963.27.camel@idefix> Hi Adam, yes, this seems to be the same bug. I just annotated ticket #10009. I hope the fix will make it into GHC 7.10.2. Can anyone say when GHC 7.10.2 will be released approximately? All the best, Wolfgang Am Dienstag, den 02.06.2015, 13:00 -0400 schrieb adam vogt: > Hi Wolfgang, > > > https://ghc.haskell.org/trac/ghc/ticket/10009 might be the same > regression (fixed in HEAD) > > > Regards, > > Adam > > > On Tue, Jun 2, 2015 at 12:28 PM, Wolfgang Jeltsch > wrote: > Hi, > > the following (contrived) code is accepted by GHC 7.8.3, but > not 7.10.1: > > > {-# LANGUAGE TypeFamilies #-} > > > > type family F a :: * > > > > type family G b :: * > > > > x :: G (F a) ~ a => F a > > x = undefined > > GHC 7.10.1 reports: > > > Could not deduce (F a0 ~ F a) > > from the context (G (F a) ~ a) > > bound by the type signature for x :: (G (F a) ~ a) => F a > > at Test.hs:7:6-23 > > NB: ?F? is a type function, and may not be injective > > The type variable ?a0? is ambiguous > > In the ambiguity check for the type signature for ?x?: > > x :: forall a. (G (F a) ~ a) => F a > > To defer the ambiguity check to use sites, enable > AllowAmbiguousTypes > > In the type signature for ?x?: x :: G (F a) ~ a => F a > > At a first look, this complaint seems reasonable, and I have > already > wondered why GHC 7.8.3 actually accepts the above code. > > From an intuitive standpoint, however, the code seems actually > acceptable to me. While it is true that type families are > generally not > injective, it is possible to derive the type a from F a by > applying G. > > It would great if this code would be accepted by GHC again and > if there > was a workaround to make it work with GHC 7.10.1. At the > moment, this > change in the type checker from 7.8.3 to 7.10.1 breaks the > incremental-computing package in a rather fundamental way. > > All the best, > Wolfgang > > _______________________________________________ > Glasgow-haskell-users mailing list > Glasgow-haskell-users at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/glasgow-haskell-users > > From g9ks157k at acme.softbase.org Tue Jun 2 22:03:03 2015 From: g9ks157k at acme.softbase.org (Wolfgang Jeltsch) Date: Wed, 03 Jun 2015 01:03:03 +0300 Subject: HEADS UP: Final call for 7.10.2 is soon In-Reply-To: References: Message-ID: <1433282583.7963.29.camel@idefix> Hi, bug #10009 appears on the status page with status ?new?, although the bug should have been fixed in HEAD. Can this fix *please* be a part of GHC 7.10.2? At the moment, this bug breaks the incremental-computing package in a nontrivial way (and I think it breaks HList too). All the best, Wolfgang Am Dienstag, den 02.06.2015, 16:31 -0500 schrieb Austin Seipp: > Hi *, > > I've just finished merging all the latest patches for GHC 7.10.2 into > the STABLE branch. All in all, we've fixed a lot of bugs (over 80 > tickets closed)! > > So, we'll probably be doing a 7.10.2 release here in a few weeks. The > tentative plan was around the 14th, although it's not set in stone. > (At worst, it would be pushed from the 14th to the 21st). > > With that in mind, if I could quickly direct your attention to the GHC > bug tracker and the status page[1] - it would be really helpful if you > check if the things you want are fixed! > > Specifically, if you want something fixed for the 7.10.2 release: > > - Make sure there is a ticket. It really needs to exist or we'll just forget! > > - If your bug is critical, please explain why! We really want to > kill showstoppers ASAP, because bugs are much cheaper to fix early. If > that's the case we can bump the priority if it's necessary to make > things clear. > > - Set the milestone to 7.10.2. It'll automatically appear on the status page. > > That should be it - we'll be monitoring the status page regularly to > keep track of new things. The current bug list is pretty small - we > may move some of them out, or fix several more. So just try to let us > know. > > As a sidenote, I'm quite happy with this release - it's fixed dozens > of tricky bugs, improved some nasty corner cases in compiler > performance, and overall seems like it will be high quality. Thanks to > everyone who submitted patches! > > I'll send out another email next week as another reminder. > > [1] https://ghc.haskell.org/trac/ghc/wiki/Status/GHC-7.10.2 > From qdunkan at gmail.com Wed Jun 3 01:36:56 2015 From: qdunkan at gmail.com (Evan Laforge) Date: Tue, 2 Jun 2015 18:36:56 -0700 Subject: ghc 7.10.1 hard lock on exit with shake, OS X 10.10 Message-ID: After I upgraded to 7.10.1 I started noticing that my shakefile would lock up on exit. It's after the 'main' function exits, and none of the shake tests have a problem, so presumably it's a GHC thing, that shake somehow causes to happen. Only kill -9 gets it to quit. Here's a stack trace from the OS X sampler: Call graph: 2801 Thread_909901 DispatchQueue_2: com.apple.libdispatch-manager (serial) 2801 _dispatch_mgr_thread (in libdispatch.dylib) + 52 [0x7fff8828ca6a] 2801 kevent64 (in libsystem_kernel.dylib) + 10 [0x7fff90ec0232] Total number in stack (recursive counted multiple, when >=5): Sort by top of stack, same collapsed (when >= 5): kevent64 (in libsystem_kernel.dylib) 2801 I know there aren't a lot of details here, but does this sound familiar to anyone? I can't see anything on https://ghc.haskell.org/trac/ghc/wiki/Status/GHC-7.10.2 that looks like this. Is there any way I can get more information I can get to report this? It used to be frequent (once in 10 runs maybe), but later became quite infrequent (once in a couple hundred runs, maybe). I downgraded to 7.8.4 and it hasn't happened again. From carter.schonwald at gmail.com Wed Jun 3 02:20:54 2015 From: carter.schonwald at gmail.com (Carter Schonwald) Date: Tue, 2 Jun 2015 22:20:54 -0400 Subject: ghc 7.10.1 hard lock on exit with shake, OS X 10.10 In-Reply-To: References: Message-ID: could you share a minimal program that reproduces the problem? On Tue, Jun 2, 2015 at 9:36 PM, Evan Laforge wrote: > After I upgraded to 7.10.1 I started noticing that my shakefile would > lock up on exit. It's after the 'main' function exits, and none of > the shake tests have a problem, so presumably it's a GHC thing, that > shake somehow causes to happen. Only kill -9 gets it to quit. Here's > a stack trace from the OS X sampler: > > Call graph: > 2801 Thread_909901 DispatchQueue_2: > com.apple.libdispatch-manager (serial) > 2801 _dispatch_mgr_thread (in libdispatch.dylib) + 52 > [0x7fff8828ca6a] > 2801 kevent64 (in libsystem_kernel.dylib) + 10 [0x7fff90ec0232] > > Total number in stack (recursive counted multiple, when >=5): > > Sort by top of stack, same collapsed (when >= 5): > kevent64 (in libsystem_kernel.dylib) 2801 > > > I know there aren't a lot of details here, but does this sound > familiar to anyone? I can't see anything on > https://ghc.haskell.org/trac/ghc/wiki/Status/GHC-7.10.2 that looks > like this. Is there any way I can get more information I can get to > report this? > > It used to be frequent (once in 10 runs maybe), but later became quite > infrequent (once in a couple hundred runs, maybe). I downgraded to > 7.8.4 and it hasn't happened again. > _______________________________________________ > Glasgow-haskell-users mailing list > Glasgow-haskell-users at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/glasgow-haskell-users > -------------- next part -------------- An HTML attachment was scrubbed... URL: From haskell at kuhtz.eu Wed Jun 3 05:20:53 2015 From: haskell at kuhtz.eu (Lars Kuhtz) Date: Tue, 2 Jun 2015 22:20:53 -0700 Subject: -prof, -threaded, and -N Message-ID: Hi, The behavior of the -N flag (without argument) with the profiling runtime seems inconsistent compared to the behavior without profiling. The following program ``` module Main where import GHC.Conc main :: IO () main = print numCapabilities ``` when compiled with `ghc -threaded -fforce-recomp Prof.hs` and run as `./Prof +RTS -N` prints `2` on my machine. When the same program is compiled with `ghc -threaded -fforce-recomp -prof Prof.hs` and executed as `./Prof +RTS -N` it prints `1`. When an argument is provided to `-N` (e.g. `./Prof +RTS -N2`) the profiling and non-profiling versions behave the same. I tested this with GHC-7.10.1 but I think that I already observed the same behavior with GHC-7.8. Is this inconsistency intended? Lars From qdunkan at gmail.com Wed Jun 3 05:27:52 2015 From: qdunkan at gmail.com (Evan Laforge) Date: Tue, 2 Jun 2015 22:27:52 -0700 Subject: ghc 7.10.1 hard lock on exit with shake, OS X 10.10 In-Reply-To: References: Message-ID: On Tue, Jun 2, 2015 at 7:20 PM, Carter Schonwald wrote: > could you share a minimal program that reproduces the problem? That's the thing, it's a thousand line shakefile that builds a 100k line program, and it's happening only rarely now. Since it happens so rarely it seems really difficult to prune away bits to see if it still happens. I suppose since the building is all just running commands, the source it's building doesn't matter, but since it's a build, it runs a different sequence of commands every time. I suppose I could "stub out" the program by replacing ghc with a shell script that sleeps and touches the output files, but it feels like I could spend days on it because there are tons of little details. I'm pretty sure it's related to the threaded runtime, because it doesn't happen without -threaded. I could try with -debug, but that probably turns off -threaded too, so no more problem. Shake is heavily threaded and nondeterministic. I haven't seen other shake users report it though. From vogt.adam at gmail.com Wed Jun 3 05:45:26 2015 From: vogt.adam at gmail.com (adam vogt) Date: Wed, 3 Jun 2015 01:45:26 -0400 Subject: HEADS UP: Final call for 7.10.2 is soon In-Reply-To: <1433282583.7963.29.camel@idefix> References: <1433282583.7963.29.camel@idefix> Message-ID: On Jun 2, 2015 6:03 PM, "Wolfgang Jeltsch" wrote: > > Hi, > > bug #10009 appears on the status page with status ?new?, although the > bug should have been fixed in HEAD. Can this fix *please* be a part of > GHC 7.10.2? At the moment, this bug breaks the incremental-computing > package in a nontrivial way (and I think it breaks HList too). Hlist 0.4 released a couple weeks ago works around #10009 by using FDs instead. User code isn't affected since the extra parameters are hidden by using the original TF. But that won't help if you were using those TFs with a gadt. -------------- next part -------------- An HTML attachment was scrubbed... URL: From haskell at kuhtz.eu Wed Jun 3 06:03:42 2015 From: haskell at kuhtz.eu (Lars Kuhtz) Date: Tue, 2 Jun 2015 23:03:42 -0700 Subject: -prof, -threaded, and -N In-Reply-To: References: Message-ID: <0334884B-2729-4E39-AEC2-2957D9B04C1A@kuhtz.eu> From https://github.com/ghc/ghc/blob/master/rts/RtsFlags.c#L1238 it seems that the behavior described in my email below is intended: ``` if (rts_argv[arg][2] == '\0') { #if defined(PROFILING) RtsFlags.ParFlags.nNodes = 1; #else RtsFlags.ParFlags.nNodes = getNumberOfProcessors(); #endif ``` So, my question is: what is the reason for this difference between the profiling and the non-profiling case? Lars > On Jun 2, 2015, at 10:20 PM, Lars Kuhtz wrote: > > Hi, > > The behavior of the -N flag (without argument) with the profiling runtime seems inconsistent compared to the behavior without profiling. The following program > > ``` > module Main where > > import GHC.Conc > > main :: IO () > main = print numCapabilities > ``` > > when compiled with `ghc -threaded -fforce-recomp Prof.hs` and run as `./Prof +RTS -N` prints `2` on my machine. When the same program is compiled with `ghc -threaded -fforce-recomp -prof Prof.hs` and executed as `./Prof +RTS -N` it prints `1`. > > When an argument is provided to `-N` (e.g. `./Prof +RTS -N2`) the profiling and non-profiling versions behave the same. > > I tested this with GHC-7.10.1 but I think that I already observed the same behavior with GHC-7.8. > > Is this inconsistency intended? > > Lars > _______________________________________________ > Glasgow-haskell-users mailing list > Glasgow-haskell-users at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/glasgow-haskell-users > From austin at well-typed.com Wed Jun 3 06:29:46 2015 From: austin at well-typed.com (Austin Seipp) Date: Wed, 3 Jun 2015 01:29:46 -0500 Subject: ghc 7.10.1 hard lock on exit with shake, OS X 10.10 In-Reply-To: References: Message-ID: Perhaps #10317 is related? https://ghc.haskell.org/trac/ghc/ticket/10317 You might try building with the latest ghc-7.10 branch. On Wed, Jun 3, 2015 at 12:27 AM, Evan Laforge wrote: > On Tue, Jun 2, 2015 at 7:20 PM, Carter Schonwald > wrote: >> could you share a minimal program that reproduces the problem? > > That's the thing, it's a thousand line shakefile that builds a 100k > line program, and it's happening only rarely now. Since it happens so > rarely it seems really difficult to prune away bits to see if it still > happens. I suppose since the building is all just running commands, > the source it's building doesn't matter, but since it's a build, it > runs a different sequence of commands every time. I suppose I could > "stub out" the program by replacing ghc with a shell script that > sleeps and touches the output files, but it feels like I could spend > days on it because there are tons of little details. > > I'm pretty sure it's related to the threaded runtime, because it > doesn't happen without -threaded. I could try with -debug, but that > probably turns off -threaded too, so no more problem. Shake is > heavily threaded and nondeterministic. I haven't seen other shake > users report it though. > _______________________________________________ > Glasgow-haskell-users mailing list > Glasgow-haskell-users at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/glasgow-haskell-users > -- Regards, Austin Seipp, Haskell Consultant Well-Typed LLP, http://www.well-typed.com/ From austin at well-typed.com Wed Jun 3 07:04:35 2015 From: austin at well-typed.com (Austin Seipp) Date: Wed, 3 Jun 2015 02:04:35 -0500 Subject: GHC Weekly News - 2015/06/03 Message-ID: (This post is available online at https://ghc.haskell.org/trac/ghc/blog/weekly20150603) Hi *, It's that time once again - to get some info on what's happening in the world of GHC! It's been a quiet few weeks as a UK Holiday punted one of GHC HQ's meetings off, and this week we were only partially there. The main point of discussion was 7.10.2, and continuing work on compiler performance. The good news is, the past few weeks have seen good work on both these fronts! == 7.10.2 status == 7.10.2 is swimming along very nicely - the [https://ghc.haskell.org/trac/ghc/wiki/Status/GHC-7.10.2 status page] shows the current set of tickets we've fixed and plan on fixing. Not much has changed from last time, except we've fixed even more bugs! We're currently sitting at about 85 bugs fixed, some of them pretty important - code generation bugs, compiler performance fixes, some RTS and event manager work. Your author is actually quite happy with what GHC 7.10.2 looks like, at this rate. == List chatter == - Austin Seipp announced that GHC 7.10.2 will be release soon, and developers/users should get bugs they want fixed reported to us ASAP so we can do something. https://mail.haskell.org/pipermail/ghc-devs/2015-June/009150.html - Mark Lentczner announced a Haskell Platform alpha featuring GHC 7.10.2 https://mail.haskell.org/pipermail/ghc-devs/2015-June/009128.html - Facundo Dominguez asks: sometimes we want to create a `static` pointer in a function with a local definition, how can we do that? The current problem is the desugarer gets in the way and current approaches are currently rejected, but Facundo has some ideas/questions about a fix. https://mail.haskell.org/pipermail/ghc-devs/2015-May/009110.html - David Macek has made great progress on getting native MSYS2 packages for windows working - which should be a great boon to all our Windows users! https://mail.haskell.org/pipermail/ghc-devs/2015-May/009089.html - Joachim Breitner announced the new GHC performance dashboard, which can be used to track all of GHC's performance-based tests over time. Whoohoo! https://mail.haskell.org/pipermail/ghc-devs/2015-May/009032.html - Joachim Breitner asked: is there a way to programmatically 'Raise a Concern' on a Phabricator commit? With the new https://perf.haskell.org/ghc/ work, it'd be nice if regressions could be automatically flagged. The current problem is there is no API endpoint, but one can be built. https://mail.haskell.org/pipermail/ghc-devs/2015-June/009128.html - Adam Gundry asked ghc-devs about some input on changes to the new typechecker plugins API. After some discussion and elbow grease, the new changes have already landed in HEAD and will be in 7.12.1. https://mail.haskell.org/pipermail/ghc-devs/2015-May/009097.html == Noteworthy commits == - Commit 45d9a15c4b85a2ed89579106bdafd84accf2cb39 - Fix a huge space leak in the mighty simplifier - Commit c89bd681d34d3339771ebdde8aa468b1d9ab042b - Fix quadratic behavior in `tidyOccName` - Commit b03f074fd51adfb9bc4f5275294712ee62741aed - ghci: Allow `:back` and `:forward` to take counts - Commit 8e4dc8fb63b8d3bfee485c1c830776f3ed704f4d - Greatly speed up `nativeCodeGen/seqBlocks` - Commit c256357242ee2dd282fd0516260edccbb7617244 - Speed up `elimCommonBlocks` by grouping blocks also by outgoing labels - Commit f5188f3acd73a07b648924a58b9882c2d0a3dbcb - Fix weird behavior of `-ignore-dot-ghci` and `-ghci-script` - Commit 4fffbc34c024231c3c9fac7a2134896cc09c7fb7 - New handling of overlapping instances in Safe Haskell - Commit f16ddcee0c64a92ab911a7841a8cf64e3ac671fd - Support stage 1 Template Haskell (non-quasi) quotes, fixes #10382 - Commit cf7573b8207bbb17c58612f3345e0b17d74cfb58 - More accurate allocation stats for `:set -s` == Closed tickets == #10407, #10408, #10177, #10359, #10403, #10248, #9579, #10415, #10419, #10427, #10429, #10397, #10422, #10335, #10366, #10110, #10397, #10349, #10244, #8555, #8799, #9131, #10396, #10354, #10278, #9899, #3533, #9950, #10092, #9950, #10430, #9682, #9584, #10446, #10410, #10298, #10449, #10399, #7695, #10261, #8292, #10360, #10126, #10317, #10101, #10322, #10313, #10471, #10473, #7170, #10473, #10423, #10466, #8695, #10461, #10052, #10370, #10425, #10452, #10474, -- Regards, Austin Seipp, Haskell Consultant Well-Typed LLP, http://www.well-typed.com/ From mechvel at botik.ru Wed Jun 3 13:40:43 2015 From: mechvel at botik.ru (Sergei Meshveliani) Date: Wed, 03 Jun 2015 16:40:43 +0300 Subject: HEADS UP: Final call for 7.10.2 is soon In-Reply-To: References: Message-ID: <1433338843.17852.23.camel@scico.botik.ru> Please, consider my recent bug report "overlapping instances in 7.10.1" (see my resent email to this list). ------ Sergei On Tue, 2015-06-02 at 16:31 -0500, Austin Seipp wrote: > Hi *, > > I've just finished merging all the latest patches for GHC 7.10.2 into > the STABLE branch. All in all, we've fixed a lot of bugs (over 80 > tickets closed)! > > So, we'll probably be doing a 7.10.2 release here in a few weeks. The > tentative plan was around the 14th, although it's not set in stone. > (At worst, it would be pushed from the 14th to the 21st). > > With that in mind, if I could quickly direct your attention to the GHC > bug tracker and the status page[1] - it would be really helpful if you > check if the things you want are fixed! > > Specifically, if you want something fixed for the 7.10.2 release: > > - Make sure there is a ticket. It really needs to exist or we'll just forget! > > - If your bug is critical, please explain why! We really want to > kill showstoppers ASAP, because bugs are much cheaper to fix early. If > that's the case we can bump the priority if it's necessary to make > things clear. > > - Set the milestone to 7.10.2. It'll automatically appear on the status page. > > That should be it - we'll be monitoring the status page regularly to > keep track of new things. The current bug list is pretty small - we > may move some of them out, or fix several more. So just try to let us > know. > > As a sidenote, I'm quite happy with this release - it's fixed dozens > of tricky bugs, improved some nasty corner cases in compiler > performance, and overall seems like it will be high quality. Thanks to > everyone who submitted patches! > > I'll send out another email next week as another reminder. > > [1] https://ghc.haskell.org/trac/ghc/wiki/Status/GHC-7.10.2 > From johan.tibell at gmail.com Wed Jun 3 15:41:38 2015 From: johan.tibell at gmail.com (Johan Tibell) Date: Wed, 3 Jun 2015 17:41:38 +0200 Subject: HEADS UP: Final call for 7.10.2 is soon In-Reply-To: <1433338843.17852.23.camel@scico.botik.ru> References: <1433338843.17852.23.camel@scico.botik.ru> Message-ID: There have been some requests for a Cabal library release for 7.10.2. I remember something about truncate directories/symbol names being an issue. I'm CC:ing the Cabal mailing list for comments. On Wed, Jun 3, 2015 at 3:40 PM, Sergei Meshveliani wrote: > Please, > consider my recent bug report > "overlapping instances in 7.10.1" > (see my resent email to this list). > > ------ > Sergei > > > > On Tue, 2015-06-02 at 16:31 -0500, Austin Seipp wrote: > > Hi *, > > > > I've just finished merging all the latest patches for GHC 7.10.2 into > > the STABLE branch. All in all, we've fixed a lot of bugs (over 80 > > tickets closed)! > > > > So, we'll probably be doing a 7.10.2 release here in a few weeks. The > > tentative plan was around the 14th, although it's not set in stone. > > (At worst, it would be pushed from the 14th to the 21st). > > > > With that in mind, if I could quickly direct your attention to the GHC > > bug tracker and the status page[1] - it would be really helpful if you > > check if the things you want are fixed! > > > > Specifically, if you want something fixed for the 7.10.2 release: > > > > - Make sure there is a ticket. It really needs to exist or we'll just > forget! > > > > - If your bug is critical, please explain why! We really want to > > kill showstoppers ASAP, because bugs are much cheaper to fix early. If > > that's the case we can bump the priority if it's necessary to make > > things clear. > > > > - Set the milestone to 7.10.2. It'll automatically appear on the > status page. > > > > That should be it - we'll be monitoring the status page regularly to > > keep track of new things. The current bug list is pretty small - we > > may move some of them out, or fix several more. So just try to let us > > know. > > > > As a sidenote, I'm quite happy with this release - it's fixed dozens > > of tricky bugs, improved some nasty corner cases in compiler > > performance, and overall seems like it will be high quality. Thanks to > > everyone who submitted patches! > > > > I'll send out another email next week as another reminder. > > > > [1] https://ghc.haskell.org/trac/ghc/wiki/Status/GHC-7.10.2 > > > > > _______________________________________________ > Glasgow-haskell-users mailing list > Glasgow-haskell-users at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/glasgow-haskell-users > -------------- next part -------------- An HTML attachment was scrubbed... URL: From anthony_clayden at clear.net.nz Wed Jun 3 23:09:39 2015 From: anthony_clayden at clear.net.nz (AntC) Date: Wed, 3 Jun 2015 23:09:39 +0000 (UTC) Subject: Closed Type Families: separate instance groups? Message-ID: Currently (GHC 7.8.3) the only form for Closed Type Families is: type family F a where ... -- list your instances here (This was considered a common use case -- for example in HList to put the type-matching instance with the non-matching, and that would be total coverage; rather than needing a type family decl and an instance decl with the instance head same as family. That was an optimisation over ...) Way back the design was more like this: type family F a type instance F (Foo b c) where F (Foo Int c) = ... F (Foo b Char) = ... type instance F (Bar e f g) where F (Bar Int f g) = ... The idea was that the separate instance groups must have non-overlapping heads. This is handy if Foo, Bar, etc are declared in separate places/modules. You can put the instances with the data decl. And quite possibly the family decl is in an imported/library module you don't want to touch. Is this separate instance group idea still a gleam in someone's eye? If not, is there some deep theoretical reason against? AntC From eir at cis.upenn.edu Thu Jun 4 00:30:09 2015 From: eir at cis.upenn.edu (Richard Eisenberg) Date: Wed, 3 Jun 2015 20:30:09 -0400 Subject: Closed Type Families: separate instance groups? In-Reply-To: References: Message-ID: <708B9380-1C71-4855-9DB1-9D66271F9C2F@cis.upenn.edu> On Jun 3, 2015, at 7:09 PM, AntC wrote: > Is this separate instance group idea still a gleam in someone's eye? > If not, is there some deep theoretical reason against? Not to my knowledge (to both questions). But I don't believe we've lost any expressiveness over the earlier version. You can always define a helper closed type family and have an open type family instance just call a closed type family. Of course, it would be nice to have *local* type families (as if, say, there were a `where` clause allowed), but this should work for you. Or does this not work in your use case? Having closed type families, as opposed to branched instances, just seemed like a cleaner way to package the new functionality. There really wasn't much to it other than aesthetics, if I recall the conversations correctly. Richard From anthony_clayden at clear.net.nz Thu Jun 4 00:53:41 2015 From: anthony_clayden at clear.net.nz (AntC) Date: Thu, 4 Jun 2015 00:53:41 +0000 (UTC) Subject: Closed Type Families: separate instance groups? References: <708B9380-1C71-4855-9DB1-9D66271F9C2F@cis.upenn.edu> Message-ID: > Richard Eisenberg cis.upenn.edu> writes: > > You can always define a helper closed type family > and have an open type family instance just call a closed type family. Thank you Richard, you mean like: type family OpenF a ... type instance OpenF (Foo b c) = FFoo (Foo b c) type family FFoo a where FFoo (Foo Int c) = ... ... OK. (Seems rather verbose.) > > Having closed type families, as opposed to branched instances, > just seemed like a cleaner way to package the new functionality. > There really wasn't much to it other than aesthetics, > if I recall the conversations correctly. I recall the conversation quite well. (In fact I think it was me who suggested type family ... where ... ) I think it was less to do with aesthetics, and more to do with reducing verbosity in a common use case. It somehow doesn't seem as clean as old-fashioned overlapping instances. (I agree it does seem cleaner than overlaps with FunDeps.) It also BTW cuts us off from using Closed Families as Associated types separated into their Class instances. I think there's two use cases going on: - one where we want to see all the instances together that fits well to type family ... where ... - t'other where we want everything to do with a type constructor together that fits better with the separate instances AntC From simonpj at microsoft.com Thu Jun 4 09:22:38 2015 From: simonpj at microsoft.com (Simon Peyton Jones) Date: Thu, 4 Jun 2015 09:22:38 +0000 Subject: Closed Type Families: separate instance groups? In-Reply-To: References: <708B9380-1C71-4855-9DB1-9D66271F9C2F@cis.upenn.edu> Message-ID: I think it's pretty good as-is. * Use an open family (with non-overlapping instances) to get yourself into part of the match space: type instance OpenF (Foo b c) = FFoo (Foo b c) * Use a closed family (with overlap and top-to-bottom matching) to deal with that part of the space: type family FFoo a where FFoo (Foo Int c) = ... Doing this was a HUGE improvement, allowing us to cleanly split the issues of top-to-bottom matching from those of non-overlapping open families. | It also BTW cuts us off from using Closed Families as Associated types | separated into their Class instances. I don't understand this comment. Can you give an example that the current setup does not handle? Simon | -----Original Message----- | From: Glasgow-haskell-users [mailto:glasgow-haskell-users- | bounces at haskell.org] On Behalf Of AntC | Sent: 04 June 2015 01:54 | To: glasgow-haskell-users at haskell.org | Subject: Re: Closed Type Families: separate instance groups? | | > Richard Eisenberg cis.upenn.edu> writes: | > | > You can always define a helper closed type family and have an open | > type family instance just call a closed type family. | | Thank you Richard, you mean like: | | type family OpenF a | | ... | | type instance OpenF (Foo b c) = FFoo (Foo b c) | type family FFoo a where | FFoo (Foo Int c) = ... | ... | | OK. (Seems rather verbose.) | | > | > Having closed type families, as opposed to branched instances, just | > seemed like a cleaner way to package the new functionality. | > There really wasn't much to it other than aesthetics, if I recall | the | > conversations correctly. | | I recall the conversation quite well. | (In fact I think it was me who suggested type family ... where ... ) I | think it was less to do with aesthetics, and more to do with reducing | verbosity in a common use case. | | It somehow doesn't seem as clean as old-fashioned overlapping | instances. | (I agree it does seem cleaner than overlaps with FunDeps.) | | It also BTW cuts us off from using Closed Families as Associated types | separated into their Class instances. | I think there's two use cases going on: | - one where we want to see all the instances together | that fits well to type family ... where ... | - t'other where we want everything to do with a type constructor | together | that fits better with the separate instances | | AntC | | | | _______________________________________________ | Glasgow-haskell-users mailing list | Glasgow-haskell-users at haskell.org | http://mail.haskell.org/cgi-bin/mailman/listinfo/glasgow-haskell-users From anthony_clayden at clear.net.nz Thu Jun 4 22:39:25 2015 From: anthony_clayden at clear.net.nz (AntC) Date: Thu, 4 Jun 2015 22:39:25 +0000 (UTC) Subject: Closed Type Families: separate instance groups? References: <708B9380-1C71-4855-9DB1-9D66271F9C2F@cis.upenn.edu> Message-ID: > Simon Peyton Jones microsoft.com> writes: > > I think it's pretty good as-is. > Thank you Simon, I'm agreeing with "pretty good", though possibly not with "pretty" ;-) > ... > * Use a closed family (with overlap and top-to-bottom matching) > to deal with that part of the space: > > Doing this was a HUGE improvement, ... (I'm not quite getting improvement over what? This was and is the only way to do overlaps with Type Families?) I'm not ever-so sure I'm seeing an improvement over overlapping class instances with FunDeps. I really really want type families to be an improvement because type manipulation in a functional language should be -- errm -- functional. > | It also BTW cuts us off from using Closed Families as Associated types > | separated into their Class instances. > > I don't understand this comment. ... I'll answer Richard's strapline at https://typesandkinds.wordpress.com/ "Who needs terms, anyway?": I need both types and terms. Yes the compiler needs first a type-solving phase before dealing with the terms. Type Families cleanly separate that off. And in a significant proportion of use cases, the type-handling is the same across many class instances. So it's more succinct to collapse the type instances into a grouped type family ... where ... There's other use cases for overlapping where you can't collapse the type-handling. So then I'm finding that my class instances have heads that repeat the type instance heads. And I would use Assoc types but the type family instances have to appear in the family, to sequence the top-to-bottom matching. > Can you give an example that the current setup does not handle? > (This is about dealing with many instances, so difficult to give a succinct example. And the current setup does handle it OK. It's just that it seems verbose, with hard to read code, compared to FunDeps. I appreciate that's in the eye of the beholder.) Take the standard example for partial overlaps. Suppose I have a class: class C a where f :: a -> F a instance C (Foo Int c) where -- I'd like to put type F (Foo Int b) = Int -- but it overlaps f (Foo x _) = x instance C (Foo b Char) where type F (Foo b Char) = Char -- non-confluent f (Foo _ y) = y Imagine there's dozens of overlapping instances. (And BTW there's no actual ambiguous usages. By construction (Foo Int b) means b /~ Char. But I have no way to declare that.) I'm also getting (in more complex examples) GHC complaining it can't infer the types for the result of f. So now I'm having to put type equality constraints on the class instances, to assure it that F comes up with the right type. This just seems easier if I have the result type as an extra param to the class, with a FunDep in the classic style: class C a b | a -> b where f :: a -> b (I can supply those more complex examples if need be, but this post is already too long.) AntC From ezyang at mit.edu Fri Jun 5 03:31:57 2015 From: ezyang at mit.edu (Edward Z. Yang) Date: Thu, 04 Jun 2015 20:31:57 -0700 Subject: [Haskell-cafe] The evil GADTs extension in ghci 7.8.4 (maybe in other versions too?) In-Reply-To: References: Message-ID: <1433475098-sup-1820@sabre> This is because -XGADTs implies -XMonoLocalBinds. Edward Excerpts from Ki Yung Ahn's message of 2015-06-04 20:29:50 -0700: > \y -> let x = (\z -> y) in x x > > is a perfectly fine there whose type is a -> a. > (1) With no options, ghci infers its type correctly. > (2) However, with -XGADTs, type check fails and raises occurs check. > (3) We can remedy this by supplying some additional options > (4) Howver, if you put -XGADTs option at the end, it fails again :( > > > kyagrd at kyahp:~$ ghci > GHCi, version 7.8.4: http://www.haskell.org/ghc/ :? for help > Loading package ghc-prim ... linking ... done. > Loading package integer-gmp ... linking ... done. > Loading package base ... linking ... done. > Prelude> :t \y -> let x = (\z -> y) in x x > \y -> let x = (\z -> y) in x x :: t -> t > Prelude> :q > Leaving GHCi. > > > kyagrd at kyahp:~$ ghci -XGADTs > GHCi, version 7.8.4: http://www.haskell.org/ghc/ :? for help > Loading package ghc-prim ... linking ... done. > Loading package integer-gmp ... linking ... done. > Loading package base ... linking ... done. > Prelude> :t \y -> let x = (\z -> y) in x x > > :1:30: > Occurs check: cannot construct the infinite type: t0 ~ t0 -> t > Relevant bindings include > x :: t0 -> t (bound at :1:11) > y :: t (bound at :1:2) > In the first argument of ?x?, namely ?x? > In the expression: x x > Prelude> :q > Leaving GHCi. > > > ~$ ghci -XGADTs -XNoMonoLocalBinds -XNoMonomorphismRestriction > GHCi, version 7.8.4: http://www.haskell.org/ghc/ :? for help > Loading package ghc-prim ... linking ... done. > Loading package integer-gmp ... linking ... done. > Loading package base ... linking ... done. > Prelude> :t \y -> let x = (\z -> y) in x x > \y -> let x = (\z -> y) in x x :: t -> t > Prelude> :q > Leaving GHCi. > > > ~$ ghci -XNoMonoLocalBinds -XNoMonomorphismRestriction -XGADTs > GHCi, version 7.8.4: http://www.haskell.org/ghc/ :? for help > Loading package ghc-prim ... linking ... done. > Loading package integer-gmp ... linking ... done. > Loading package base ... linking ... done. > Prelude> :t \y -> let x = (\z -> y) in x x > > :1:30: > Occurs check: cannot construct the infinite type: t0 ~ t0 -> t > Relevant bindings include > x :: t0 -> t (bound at :1:11) > y :: t (bound at :1:2) > In the first argument of ?x?, namely ?x? > From kyagrd at gmail.com Fri Jun 5 03:37:27 2015 From: kyagrd at gmail.com (Ki Yung Ahn) Date: Thu, 04 Jun 2015 20:37:27 -0700 Subject: [Haskell-cafe] The evil GADTs extension in ghci 7.8.4 (maybe in other versions too?) In-Reply-To: <1433475098-sup-1820@sabre> References: <1433475098-sup-1820@sabre> Message-ID: Such order dependent could be very confusing for the users. I thought I turned off certain feature but some other extension turning it on is strange. Wouldn't it be better to decouple GADT and MonoLocalBinds? 2015? 06? 04? 20:31? Edward Z. Yang ?(?) ? ?: > This is because -XGADTs implies -XMonoLocalBinds. > > Edward > > Excerpts from Ki Yung Ahn's message of 2015-06-04 20:29:50 -0700: >> \y -> let x = (\z -> y) in x x >> >> is a perfectly fine there whose type is a -> a. >> (1) With no options, ghci infers its type correctly. >> (2) However, with -XGADTs, type check fails and raises occurs check. >> (3) We can remedy this by supplying some additional options >> (4) Howver, if you put -XGADTs option at the end, it fails again :( >> >> >> kyagrd at kyahp:~$ ghci >> GHCi, version 7.8.4: http://www.haskell.org/ghc/ :? for help >> Loading package ghc-prim ... linking ... done. >> Loading package integer-gmp ... linking ... done. >> Loading package base ... linking ... done. >> Prelude> :t \y -> let x = (\z -> y) in x x >> \y -> let x = (\z -> y) in x x :: t -> t >> Prelude> :q >> Leaving GHCi. >> >> >> kyagrd at kyahp:~$ ghci -XGADTs >> GHCi, version 7.8.4: http://www.haskell.org/ghc/ :? for help >> Loading package ghc-prim ... linking ... done. >> Loading package integer-gmp ... linking ... done. >> Loading package base ... linking ... done. >> Prelude> :t \y -> let x = (\z -> y) in x x >> >> :1:30: >> Occurs check: cannot construct the infinite type: t0 ~ t0 -> t >> Relevant bindings include >> x :: t0 -> t (bound at :1:11) >> y :: t (bound at :1:2) >> In the first argument of ?x?, namely ?x? >> In the expression: x x >> Prelude> :q >> Leaving GHCi. >> >> >> ~$ ghci -XGADTs -XNoMonoLocalBinds -XNoMonomorphismRestriction >> GHCi, version 7.8.4: http://www.haskell.org/ghc/ :? for help >> Loading package ghc-prim ... linking ... done. >> Loading package integer-gmp ... linking ... done. >> Loading package base ... linking ... done. >> Prelude> :t \y -> let x = (\z -> y) in x x >> \y -> let x = (\z -> y) in x x :: t -> t >> Prelude> :q >> Leaving GHCi. >> >> >> ~$ ghci -XNoMonoLocalBinds -XNoMonomorphismRestriction -XGADTs >> GHCi, version 7.8.4: http://www.haskell.org/ghc/ :? for help >> Loading package ghc-prim ... linking ... done. >> Loading package integer-gmp ... linking ... done. >> Loading package base ... linking ... done. >> Prelude> :t \y -> let x = (\z -> y) in x x >> >> :1:30: >> Occurs check: cannot construct the infinite type: t0 ~ t0 -> t >> Relevant bindings include >> x :: t0 -> t (bound at :1:11) >> y :: t (bound at :1:2) >> In the first argument of ?x?, namely ?x? >> > _______________________________________________ > Glasgow-haskell-users mailing list > Glasgow-haskell-users at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/glasgow-haskell-users > From ezyang at mit.edu Fri Jun 5 03:43:53 2015 From: ezyang at mit.edu (Edward Z. Yang) Date: Thu, 04 Jun 2015 20:43:53 -0700 Subject: [Haskell-cafe] The evil GADTs extension in ghci 7.8.4 (maybe in other versions too?) In-Reply-To: References: <1433475098-sup-1820@sabre> Message-ID: <1433475711-sup-8101@sabre> GHC used to always generalize let-bindings, but our experience with GADTs lead us to decide that let should not be generalized with GADTs. So, it's not like we /wanted/ MonoLocalBinds, but that having them makes the GADT machinery simpler. This blog post gives more details on the matter: https://ghc.haskell.org/trac/ghc/blog/LetGeneralisationInGhc7 Edward Excerpts from Ki Yung Ahn's message of 2015-06-04 20:37:27 -0700: > Such order dependent could be very confusing for the users. I thought I > turned off certain feature but some other extension turning it on is > strange. Wouldn't it be better to decouple GADT and MonoLocalBinds? > > 2015? 06? 04? 20:31? Edward Z. Yang ?(?) ? ?: > > This is because -XGADTs implies -XMonoLocalBinds. > > > > Edward > > > > Excerpts from Ki Yung Ahn's message of 2015-06-04 20:29:50 -0700: > >> \y -> let x = (\z -> y) in x x > >> > >> is a perfectly fine there whose type is a -> a. > >> (1) With no options, ghci infers its type correctly. > >> (2) However, with -XGADTs, type check fails and raises occurs check. > >> (3) We can remedy this by supplying some additional options > >> (4) Howver, if you put -XGADTs option at the end, it fails again :( > >> > >> > >> kyagrd at kyahp:~$ ghci > >> GHCi, version 7.8.4: http://www.haskell.org/ghc/ :? for help > >> Loading package ghc-prim ... linking ... done. > >> Loading package integer-gmp ... linking ... done. > >> Loading package base ... linking ... done. > >> Prelude> :t \y -> let x = (\z -> y) in x x > >> \y -> let x = (\z -> y) in x x :: t -> t > >> Prelude> :q > >> Leaving GHCi. > >> > >> > >> kyagrd at kyahp:~$ ghci -XGADTs > >> GHCi, version 7.8.4: http://www.haskell.org/ghc/ :? for help > >> Loading package ghc-prim ... linking ... done. > >> Loading package integer-gmp ... linking ... done. > >> Loading package base ... linking ... done. > >> Prelude> :t \y -> let x = (\z -> y) in x x > >> > >> :1:30: > >> Occurs check: cannot construct the infinite type: t0 ~ t0 -> t > >> Relevant bindings include > >> x :: t0 -> t (bound at :1:11) > >> y :: t (bound at :1:2) > >> In the first argument of ?x?, namely ?x? > >> In the expression: x x > >> Prelude> :q > >> Leaving GHCi. > >> > >> > >> ~$ ghci -XGADTs -XNoMonoLocalBinds -XNoMonomorphismRestriction > >> GHCi, version 7.8.4: http://www.haskell.org/ghc/ :? for help > >> Loading package ghc-prim ... linking ... done. > >> Loading package integer-gmp ... linking ... done. > >> Loading package base ... linking ... done. > >> Prelude> :t \y -> let x = (\z -> y) in x x > >> \y -> let x = (\z -> y) in x x :: t -> t > >> Prelude> :q > >> Leaving GHCi. > >> > >> > >> ~$ ghci -XNoMonoLocalBinds -XNoMonomorphismRestriction -XGADTs > >> GHCi, version 7.8.4: http://www.haskell.org/ghc/ :? for help > >> Loading package ghc-prim ... linking ... done. > >> Loading package integer-gmp ... linking ... done. > >> Loading package base ... linking ... done. > >> Prelude> :t \y -> let x = (\z -> y) in x x > >> > >> :1:30: > >> Occurs check: cannot construct the infinite type: t0 ~ t0 -> t > >> Relevant bindings include > >> x :: t0 -> t (bound at :1:11) > >> y :: t (bound at :1:2) > >> In the first argument of ?x?, namely ?x? > >> > > _______________________________________________ > > Glasgow-haskell-users mailing list > > Glasgow-haskell-users at haskell.org > > http://mail.haskell.org/cgi-bin/mailman/listinfo/glasgow-haskell-users > > > From anthony_clayden at clear.net.nz Sat Jun 6 06:04:37 2015 From: anthony_clayden at clear.net.nz (AntC) Date: Sat, 6 Jun 2015 06:04:37 +0000 (UTC) Subject: Closed Type Families: type checking dumbness? [was: separate instance groups] Message-ID: > From: AntC > Date: 2015-06-04 22:39:25 GMT > > Take the standard example for partial overlaps. > Suppose I have a class: ... > I'm also getting (in more complex examples) > GHC complaining it can't infer the types > for the result of f. > So now I'm having to put type equality > constraints on the class instances, > to assure it that F comes up with > the right type. In a reduced example, I'm still getting poor type checking. This is GHC 7.8.3. This seems so dumb, I'm suspecting a defect, It's similar to but much more glaring than: https://ghc.haskell.org/trac/ghc/ticket/10227 https://ghc.haskell.org/trac/ghc/ticket/9918 {-# LANGUAGE TypeFamilies, FlexibleInstances #-} module ClosedTypeFamily where data Foo b c = Foo b c deriving (Eq, Read, Show) type family F a where F (Foo Int c) = Int -- Foo Int is first instance F (Foo b Char) = Char class C a where f :: a -> F a instance C (Foo Int c) where -- compiles OK f (Foo x _) = x instance (F (Foo b Char) ~ Char) => C (Foo b Char) where f (Foo _ y) = y needs the eq constraint. Without it, GHC complains: Couldn't match expected type ?F (Foo b Char)? with actual type ?Char? Relevant bindings include f :: Foo b Char -> F (Foo b Char) In the expression: y In an equation for ?f?: f (Foo _ y) = y Note that if I change the sequence of the family instances for F, then GHC instead complains about the class instance for (Foo Int c). OK these are overlapping class instances. But GHC's usual behaviour (without closed type families) is to postpone complaining until and unless a usage (Foo Int Char) actually turns up. BTW if I put a first family instance F (Foo Int Char) = Int to explicitly catch the overlap, then GHC complains about **both** class instances. Reminder [to Richard] I need not only types but also terms. AntC From eir at cis.upenn.edu Sun Jun 7 11:27:12 2015 From: eir at cis.upenn.edu (Richard Eisenberg) Date: Sun, 7 Jun 2015 07:27:12 -0400 Subject: Closed Type Families: type checking dumbness? [was: separate instance groups] In-Reply-To: References: Message-ID: <16DBFE24-B570-4B5D-B30F-E11E97E1B63F@cis.upenn.edu> This is all expected behavior. GHC's lazy overlap checking for class instances simply cannot apply to type families -- it would be unsound. I'm afraid I don't see what can be improved here. Richard On Jun 6, 2015, at 2:04 AM, AntC wrote: >> From: AntC >> Date: 2015-06-04 22:39:25 GMT >> >> Take the standard example for partial overlaps. >> Suppose I have a class: ... > >> I'm also getting (in more complex examples) >> GHC complaining it can't infer the types >> for the result of f. >> So now I'm having to put type equality >> constraints on the class instances, >> to assure it that F comes up with >> the right type. > > In a reduced example, I'm still getting > poor type checking. This is GHC 7.8.3. > This seems so dumb, I'm suspecting a defect, > It's similar to > but much more glaring than: > https://ghc.haskell.org/trac/ghc/ticket/10227 > https://ghc.haskell.org/trac/ghc/ticket/9918 > > {-# LANGUAGE TypeFamilies, > FlexibleInstances > #-} > module ClosedTypeFamily where > > data Foo b c = Foo b c deriving (Eq, Read, Show) > > type family F a where > F (Foo Int c) = Int -- Foo Int is first instance > F (Foo b Char) = Char > > class C a where f :: a -> F a > > instance C (Foo Int c) where -- compiles OK > f (Foo x _) = x > > instance (F (Foo b Char) ~ Char) => C (Foo b Char) where > f (Foo _ y) = y > > needs the eq constraint. Without it, GHC complains: > Couldn't match expected type ?F (Foo b Char)? > with actual type ?Char? > Relevant bindings include > f :: Foo b Char -> F (Foo b Char) > In the expression: y > In an equation for ?f?: f (Foo _ y) = y > > Note that if I change the sequence > of the family instances for F, > then GHC instead complains > about the class instance for (Foo Int c). > > OK these are overlapping class instances. > But GHC's usual behaviour > (without closed type families) > is to postpone complaining > until and unless a usage > (Foo Int Char) actually turns up. > > BTW if I put a first family instance > F (Foo Int Char) = Int > to explicitly catch the overlap, > then GHC complains about **both** class instances. > > Reminder [to Richard] > I need not only types but also terms. > > AntC > _______________________________________________ > Glasgow-haskell-users mailing list > Glasgow-haskell-users at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/glasgow-haskell-users > From dan.doel at gmail.com Sun Jun 7 15:12:15 2015 From: dan.doel at gmail.com (Dan Doel) Date: Sun, 7 Jun 2015 11:12:15 -0400 Subject: Closed Type Families: type checking dumbness? [was: separate instance groups] In-Reply-To: <16DBFE24-B570-4B5D-B30F-E11E97E1B63F@cis.upenn.edu> References: <16DBFE24-B570-4B5D-B30F-E11E97E1B63F@cis.upenn.edu> Message-ID: It seems to me the problem is that there's no way to define classes by consecutive cases to match the family definitions. I don't know what a good syntax for that would be, since 'where' syntax is taken for those. But it seems like it would correspond fill the hole here. On Sun, Jun 7, 2015 at 7:27 AM, Richard Eisenberg wrote: > This is all expected behavior. GHC's lazy overlap checking for class > instances simply cannot apply to type families -- it would be unsound. I'm > afraid I don't see what can be improved here. > > Richard > > On Jun 6, 2015, at 2:04 AM, AntC wrote: > > >> From: AntC > >> Date: 2015-06-04 22:39:25 GMT > >> > >> Take the standard example for partial overlaps. > >> Suppose I have a class: ... > > > >> I'm also getting (in more complex examples) > >> GHC complaining it can't infer the types > >> for the result of f. > >> So now I'm having to put type equality > >> constraints on the class instances, > >> to assure it that F comes up with > >> the right type. > > > > In a reduced example, I'm still getting > > poor type checking. This is GHC 7.8.3. > > This seems so dumb, I'm suspecting a defect, > > It's similar to > > but much more glaring than: > > https://ghc.haskell.org/trac/ghc/ticket/10227 > > https://ghc.haskell.org/trac/ghc/ticket/9918 > > > > {-# LANGUAGE TypeFamilies, > > FlexibleInstances > > #-} > > module ClosedTypeFamily where > > > > data Foo b c = Foo b c deriving (Eq, Read, Show) > > > > type family F a where > > F (Foo Int c) = Int -- Foo Int is first instance > > F (Foo b Char) = Char > > > > class C a where f :: a -> F a > > > > instance C (Foo Int c) where -- compiles OK > > f (Foo x _) = x > > > > instance (F (Foo b Char) ~ Char) => C (Foo b Char) where > > f (Foo _ y) = y > > > > needs the eq constraint. Without it, GHC complains: > > Couldn't match expected type ?F (Foo b Char)? > > with actual type ?Char? > > Relevant bindings include > > f :: Foo b Char -> F (Foo b Char) > > In the expression: y > > In an equation for ?f?: f (Foo _ y) = y > > > > Note that if I change the sequence > > of the family instances for F, > > then GHC instead complains > > about the class instance for (Foo Int c). > > > > OK these are overlapping class instances. > > But GHC's usual behaviour > > (without closed type families) > > is to postpone complaining > > until and unless a usage > > (Foo Int Char) actually turns up. > > > > BTW if I put a first family instance > > F (Foo Int Char) = Int > > to explicitly catch the overlap, > > then GHC complains about **both** class instances. > > > > Reminder [to Richard] > > I need not only types but also terms. > > > > AntC > > _______________________________________________ > > Glasgow-haskell-users mailing list > > Glasgow-haskell-users at haskell.org > > http://mail.haskell.org/cgi-bin/mailman/listinfo/glasgow-haskell-users > > > > _______________________________________________ > Glasgow-haskell-users mailing list > Glasgow-haskell-users at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/glasgow-haskell-users > -------------- next part -------------- An HTML attachment was scrubbed... URL: From vogt.adam at gmail.com Sun Jun 7 16:36:07 2015 From: vogt.adam at gmail.com (adam vogt) Date: Sun, 7 Jun 2015 12:36:07 -0400 Subject: Closed Type Families: type checking dumbness? [was: separate instance groups] In-Reply-To: References: <16DBFE24-B570-4B5D-B30F-E11E97E1B63F@cis.upenn.edu> Message-ID: Hi, AntC's f can be done without -XOverlappingInstances < http://lpaste.net/7559485273839501312>, using the trick didn't work in #9918. I'm not sure extra syntax is justified to clean up this rare case. Regards, Adam On Sun, Jun 7, 2015 at 11:12 AM, Dan Doel wrote: > It seems to me the problem is that there's no way to define classes by > consecutive cases to match the family definitions. I don't know what a good > syntax for that would be, since 'where' syntax is taken for those. But it > seems like it would correspond fill the hole here. > > On Sun, Jun 7, 2015 at 7:27 AM, Richard Eisenberg > wrote: > >> This is all expected behavior. GHC's lazy overlap checking for class >> instances simply cannot apply to type families -- it would be unsound. I'm >> afraid I don't see what can be improved here. >> >> Richard >> >> On Jun 6, 2015, at 2:04 AM, AntC wrote: >> >> >> From: AntC >> >> Date: 2015-06-04 22:39:25 GMT >> >> >> >> Take the standard example for partial overlaps. >> >> Suppose I have a class: ... >> > >> >> I'm also getting (in more complex examples) >> >> GHC complaining it can't infer the types >> >> for the result of f. >> >> So now I'm having to put type equality >> >> constraints on the class instances, >> >> to assure it that F comes up with >> >> the right type. >> > >> > In a reduced example, I'm still getting >> > poor type checking. This is GHC 7.8.3. >> > This seems so dumb, I'm suspecting a defect, >> > It's similar to >> > but much more glaring than: >> > https://ghc.haskell.org/trac/ghc/ticket/10227 >> > https://ghc.haskell.org/trac/ghc/ticket/9918 >> > >> > {-# LANGUAGE TypeFamilies, >> > FlexibleInstances >> > #-} >> > module ClosedTypeFamily where >> > >> > data Foo b c = Foo b c deriving (Eq, Read, Show) >> > >> > type family F a where >> > F (Foo Int c) = Int -- Foo Int is first instance >> > F (Foo b Char) = Char >> > >> > class C a where f :: a -> F a >> > >> > instance C (Foo Int c) where -- compiles OK >> > f (Foo x _) = x >> > >> > instance (F (Foo b Char) ~ Char) => C (Foo b Char) where >> > f (Foo _ y) = y >> > >> > needs the eq constraint. Without it, GHC complains: >> > Couldn't match expected type ?F (Foo b Char)? >> > with actual type ?Char? >> > Relevant bindings include >> > f :: Foo b Char -> F (Foo b Char) >> > In the expression: y >> > In an equation for ?f?: f (Foo _ y) = y >> > >> > Note that if I change the sequence >> > of the family instances for F, >> > then GHC instead complains >> > about the class instance for (Foo Int c). >> > >> > OK these are overlapping class instances. >> > But GHC's usual behaviour >> > (without closed type families) >> > is to postpone complaining >> > until and unless a usage >> > (Foo Int Char) actually turns up. >> > >> > BTW if I put a first family instance >> > F (Foo Int Char) = Int >> > to explicitly catch the overlap, >> > then GHC complains about **both** class instances. >> > >> > Reminder [to Richard] >> > I need not only types but also terms. >> > >> > AntC >> > _______________________________________________ >> > Glasgow-haskell-users mailing list >> > Glasgow-haskell-users at haskell.org >> > http://mail.haskell.org/cgi-bin/mailman/listinfo/glasgow-haskell-users >> > >> >> _______________________________________________ >> Glasgow-haskell-users mailing list >> Glasgow-haskell-users at haskell.org >> http://mail.haskell.org/cgi-bin/mailman/listinfo/glasgow-haskell-users >> > > > _______________________________________________ > Glasgow-haskell-users mailing list > Glasgow-haskell-users at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/glasgow-haskell-users > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From eir at cis.upenn.edu Sun Jun 7 18:36:25 2015 From: eir at cis.upenn.edu (Richard Eisenberg) Date: Sun, 7 Jun 2015 14:36:25 -0400 Subject: Closed Type Families: type checking dumbness? [was: separate instance groups] In-Reply-To: References: <16DBFE24-B570-4B5D-B30F-E11E97E1B63F@cis.upenn.edu> Message-ID: That's right. You're suggesting instance chains [1][2]. [1]: https://ghc.haskell.org/trac/ghc/ticket/9334 [2]: http://web.cecs.pdx.edu/~mpj/pubs/instancechains.pdf Richard On Jun 7, 2015, at 11:12 AM, Dan Doel wrote: > It seems to me the problem is that there's no way to define classes by consecutive cases to match the family definitions. I don't know what a good syntax for that would be, since 'where' syntax is taken for those. But it seems like it would correspond fill the hole here. > > On Sun, Jun 7, 2015 at 7:27 AM, Richard Eisenberg wrote: > This is all expected behavior. GHC's lazy overlap checking for class instances simply cannot apply to type families -- it would be unsound. I'm afraid I don't see what can be improved here. > > Richard > > On Jun 6, 2015, at 2:04 AM, AntC wrote: > > >> From: AntC > >> Date: 2015-06-04 22:39:25 GMT > >> > >> Take the standard example for partial overlaps. > >> Suppose I have a class: ... > > > >> I'm also getting (in more complex examples) > >> GHC complaining it can't infer the types > >> for the result of f. > >> So now I'm having to put type equality > >> constraints on the class instances, > >> to assure it that F comes up with > >> the right type. > > > > In a reduced example, I'm still getting > > poor type checking. This is GHC 7.8.3. > > This seems so dumb, I'm suspecting a defect, > > It's similar to > > but much more glaring than: > > https://ghc.haskell.org/trac/ghc/ticket/10227 > > https://ghc.haskell.org/trac/ghc/ticket/9918 > > > > {-# LANGUAGE TypeFamilies, > > FlexibleInstances > > #-} > > module ClosedTypeFamily where > > > > data Foo b c = Foo b c deriving (Eq, Read, Show) > > > > type family F a where > > F (Foo Int c) = Int -- Foo Int is first instance > > F (Foo b Char) = Char > > > > class C a where f :: a -> F a > > > > instance C (Foo Int c) where -- compiles OK > > f (Foo x _) = x > > > > instance (F (Foo b Char) ~ Char) => C (Foo b Char) where > > f (Foo _ y) = y > > > > needs the eq constraint. Without it, GHC complains: > > Couldn't match expected type ?F (Foo b Char)? > > with actual type ?Char? > > Relevant bindings include > > f :: Foo b Char -> F (Foo b Char) > > In the expression: y > > In an equation for ?f?: f (Foo _ y) = y > > > > Note that if I change the sequence > > of the family instances for F, > > then GHC instead complains > > about the class instance for (Foo Int c). > > > > OK these are overlapping class instances. > > But GHC's usual behaviour > > (without closed type families) > > is to postpone complaining > > until and unless a usage > > (Foo Int Char) actually turns up. > > > > BTW if I put a first family instance > > F (Foo Int Char) = Int > > to explicitly catch the overlap, > > then GHC complains about **both** class instances. > > > > Reminder [to Richard] > > I need not only types but also terms. > > > > AntC > > _______________________________________________ > > Glasgow-haskell-users mailing list > > Glasgow-haskell-users at haskell.org > > http://mail.haskell.org/cgi-bin/mailman/listinfo/glasgow-haskell-users > > > > _______________________________________________ > Glasgow-haskell-users mailing list > Glasgow-haskell-users at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/glasgow-haskell-users > -------------- next part -------------- An HTML attachment was scrubbed... URL: From anthony_clayden at clear.net.nz Mon Jun 8 09:49:09 2015 From: anthony_clayden at clear.net.nz (AntC) Date: Mon, 8 Jun 2015 09:49:09 +0000 (UTC) Subject: Closed Type Families: type checking dumbness? [was: separate instance groups] References: <16DBFE24-B570-4B5D-B30F-E11E97E1B63F@cis.upenn.edu> Message-ID: > Richard Eisenberg writes: > > This is all expected behavior. ... Thank you Richard. So to be clear what it is that's expected: For any class with overlapping instances that calls on a Closed Type Family, for all [**] instances, expect to put a type equality constraint, whose LHS is exactly the instance head, and whose RHS is exactly the RHS of the corresponding type family equation. IOW expect the type equation to appear twice (with `=` changed to `~`, modulo alpha renaming). Note [**] not quite all instances. The instance whose head is the first family equation can have the constraint omitted. > GHC's lazy overlap checking for class instances ... Hmm? I don't think it's the lazy checking of whether overlapping instances apply at a use site. I think it's the eager checking at the instance declaration. > ... I'm afraid I don't see what can be improved here. Two suggestions: 1. Automatically generate the type eq constraint. (Or at least suggest that as a Possible fix in the error message.) 2. Don't bother with a type family in such cases. Instead use Overlaps with FunDeps. (And needs UndecidableInstances.) > > On Jun 6, 2015, at 2:04 AM, AntC wrote: > > needs the eq constraint. Without it, GHC complains: > > Couldn't match expected type ?F (Foo b Char)? > > with actual type ?Char? > > Relevant bindings include > > f :: Foo b Char -> F (Foo b Char) > > In the expression: y > > In an equation for ?f?: f (Foo _ y) = y > > From anthony_clayden at clear.net.nz Mon Jun 8 10:03:13 2015 From: anthony_clayden at clear.net.nz (AntC) Date: Mon, 8 Jun 2015 10:03:13 +0000 (UTC) Subject: Closed Type Families: type checking dumbness? [was: separate instance groups] References: <16DBFE24-B570-4B5D-B30F-E11E97E1B63F@cis.upenn.edu> Message-ID: > Dan Doel writes: > > It seems to me the problem is that there's no way > to define classes by consecutive cases to match the family definitions. Thanks Dan, yes we've an impedance mis-match. Closed logic for type families; Open (or Distributed) logic for class instances. I see two possible fixes: 1. Closed logic for class instances > I don't know what a good syntax for that would be, > since 'where' syntax is taken for those. Indeed. We could follow SQL and use 'HAVING' ;-) 2. Open/Distributed logic for type families (and class instances). Take the example type family: > >? ? type family F a? ? where > >? ? ? F (Foo Int c)? = Int? > >? ? ? F (Foo b Char) = Char For instance selection to move confidently from the first to the second equation, it must satisfy itself that Foo's first arg could not possibly be Int. ie (b /~ Int) Let's expose the compiler's internal workings into the surface lang. And annotate that on the second equation as F (Foo b Char) | (b /~ Int) = Char This mirrors the syntax for pattern guards. Now no usage site could ever match both equations. (And we can prove that as we validate each instance.) So we could 'float' the type instances away to appear with the class instances -- even as Associated types. (And we'd need type disequality guards on the class instances.) AntC From jhala at cs.ucsd.edu Wed Jun 10 04:18:30 2015 From: jhala at cs.ucsd.edu (Ranjit Jhala) Date: Tue, 9 Jun 2015 21:18:30 -0700 Subject: cannot build 'vector' with profiling Message-ID: Hi all, I cannot build 'vector' (or 'cmdargs') with profiling on. specifically when I run: $ cabal install --enable-executable-profiling --enable-library-profiling --ghc-options="-O2 -rtsopts -prof -auto-all -caf-all" vector I get the message: Perhaps you haven't installed the "p_dyn" libraries for package ?integer-gmp? https://ghc.haskell.org/trac/ghc/ticket/8677 Per some advice I tried to add the '--disable-shared' $ cabal install --disable-shared --enable-executable-profiling --enable-library-profiling --ghc-options="-O2 -rtsopts -prof -auto-all -caf-all" vector but then I get this: Loading package primitive-0.6 ... : can't load .so/.DLL for: libHSprimitive-0.6.dylib (dlopen(libHSprimitive-0.6.dylib, 9): image not found) Any idea whats going on or for any work arounds? Pretty stumped! Thanks in advance! Ranjit. -------------- next part -------------- An HTML attachment was scrubbed... URL: From carter.schonwald at gmail.com Wed Jun 10 11:59:02 2015 From: carter.schonwald at gmail.com (Carter Schonwald) Date: Wed, 10 Jun 2015 07:59:02 -0400 Subject: cannot build 'vector' with profiling In-Reply-To: References: Message-ID: What ghc version and how was it built? On Wednesday, June 10, 2015, Ranjit Jhala wrote: > Hi all, > > I cannot build 'vector' (or 'cmdargs') with profiling on. > > specifically when I run: > > $ cabal install --enable-executable-profiling > --enable-library-profiling --ghc-options="-O2 -rtsopts -prof -auto-all > -caf-all" vector > > > I get the message: > > Perhaps you haven't installed the "p_dyn" libraries for package > ?integer-gmp? > > https://ghc.haskell.org/trac/ghc/ticket/8677 > > Per some advice I tried to add the '--disable-shared' > > > $ cabal install --disable-shared --enable-executable-profiling > --enable-library-profiling --ghc-options="-O2 -rtsopts -prof -auto-all > -caf-all" vector > > but then I get this: > > Loading package primitive-0.6 ... : can't load .so/.DLL > for: libHSprimitive-0.6.dylib (dlopen(libHSprimitive-0.6.dylib, 9): image > not found) > > > Any idea whats going on or for any work arounds? Pretty stumped! Thanks in > advance! > > Ranjit. > -------------- next part -------------- An HTML attachment was scrubbed... URL: From jhala at cs.ucsd.edu Wed Jun 10 13:26:55 2015 From: jhala at cs.ucsd.edu (Ranjit Jhala) Date: Wed, 10 Jun 2015 06:26:55 -0700 Subject: cannot build 'vector' with profiling In-Reply-To: References: Message-ID: ah, my bad I thought I'd included that -- this is ghc 7.8.3, on MacOS, installed from https://ghcformacosx.github.io ... Should I just move to 7.10? On Wed, Jun 10, 2015 at 4:59 AM, Carter Schonwald < carter.schonwald at gmail.com> wrote: > What ghc version and how was it built? > > > On Wednesday, June 10, 2015, Ranjit Jhala wrote: > >> Hi all, >> >> I cannot build 'vector' (or 'cmdargs') with profiling on. >> >> specifically when I run: >> >> $ cabal install --enable-executable-profiling >> --enable-library-profiling --ghc-options="-O2 -rtsopts -prof -auto-all >> -caf-all" vector >> >> >> I get the message: >> >> Perhaps you haven't installed the "p_dyn" libraries for package >> ?integer-gmp? >> >> https://ghc.haskell.org/trac/ghc/ticket/8677 >> >> Per some advice I tried to add the '--disable-shared' >> >> >> $ cabal install --disable-shared --enable-executable-profiling >> --enable-library-profiling --ghc-options="-O2 -rtsopts -prof -auto-all >> -caf-all" vector >> >> but then I get this: >> >> Loading package primitive-0.6 ... : can't load .so/.DLL >> for: libHSprimitive-0.6.dylib (dlopen(libHSprimitive-0.6.dylib, 9): image >> not found) >> >> >> Any idea whats going on or for any work arounds? Pretty stumped! Thanks >> in advance! >> >> Ranjit. >> > -- Ranjit. -------------- next part -------------- An HTML attachment was scrubbed... URL: From wren at community.haskell.org Wed Jun 10 18:50:13 2015 From: wren at community.haskell.org (wren romano) Date: Wed, 10 Jun 2015 14:50:13 -0400 Subject: [Haskell-cafe] The evil GADTs extension in ghci 7.8.4 (maybe in other versions too?) In-Reply-To: <1433475711-sup-8101@sabre> References: <1433475098-sup-1820@sabre> <1433475711-sup-8101@sabre> Message-ID: On Thu, Jun 4, 2015 at 11:43 PM, Edward Z. Yang wrote: > GHC used to always generalize let-bindings, but our experience > with GADTs lead us to decide that let should not be generalized > with GADTs. So, it's not like we /wanted/ MonoLocalBinds, but > that having them makes the GADT machinery simpler. > > This blog post gives more details on the matter: > https://ghc.haskell.org/trac/ghc/blog/LetGeneralisationInGhc7 The fact that -XGADTs (in isolation) implies -XMonoLocalBinds isn't the problem. The problem is, the order in which language pragma are offered should not matter. Whether I say {-# LANGUAGE GADTs, NoMonoLocalBinds #-} or {-# LANGUAGE NoMonoLocalBinds, GADTs #-} shouldn't matter. Both should mean the same thing, regardless of how annoying it may be to work in that language. -- Live well, ~wren From carter.schonwald at gmail.com Thu Jun 11 04:41:07 2015 From: carter.schonwald at gmail.com (Carter Schonwald) Date: Thu, 11 Jun 2015 00:41:07 -0400 Subject: cannot build 'vector' with profiling In-Reply-To: References: Message-ID: why were you trying to build profiling dylibs? i thought we only support static linked profiling libs? (i could be wrong though) On Wed, Jun 10, 2015 at 9:26 AM, Ranjit Jhala wrote: > ah, my bad I thought I'd included that -- this is ghc 7.8.3, on MacOS, > installed from https://ghcformacosx.github.io ... > > Should I just move to 7.10? > > On Wed, Jun 10, 2015 at 4:59 AM, Carter Schonwald < > carter.schonwald at gmail.com> wrote: > >> What ghc version and how was it built? >> >> >> On Wednesday, June 10, 2015, Ranjit Jhala wrote: >> >>> Hi all, >>> >>> I cannot build 'vector' (or 'cmdargs') with profiling on. >>> >>> specifically when I run: >>> >>> $ cabal install --enable-executable-profiling >>> --enable-library-profiling --ghc-options="-O2 -rtsopts -prof -auto-all >>> -caf-all" vector >>> >>> >>> I get the message: >>> >>> Perhaps you haven't installed the "p_dyn" libraries for package >>> ?integer-gmp? >>> >>> https://ghc.haskell.org/trac/ghc/ticket/8677 >>> >>> Per some advice I tried to add the '--disable-shared' >>> >>> >>> $ cabal install --disable-shared --enable-executable-profiling >>> --enable-library-profiling --ghc-options="-O2 -rtsopts -prof -auto-all >>> -caf-all" vector >>> >>> but then I get this: >>> >>> Loading package primitive-0.6 ... : can't load >>> .so/.DLL for: libHSprimitive-0.6.dylib (dlopen(libHSprimitive-0.6.dylib, >>> 9): image not found) >>> >>> >>> Any idea whats going on or for any work arounds? Pretty stumped! Thanks >>> in advance! >>> >>> Ranjit. >>> >> > > > -- > Ranjit. > -------------- next part -------------- An HTML attachment was scrubbed... URL: From jhala at cs.ucsd.edu Thu Jun 11 04:51:30 2015 From: jhala at cs.ucsd.edu (Ranjit Jhala) Date: Wed, 10 Jun 2015 21:51:30 -0700 Subject: cannot build 'vector' with profiling In-Reply-To: References: Message-ID: ?Hi Carter, Are you referring to the '--disable-shared' flag? If so -- I added it because otherwise I got a bunch of errors about: Perhaps you haven't installed the "p_dyn" ? ? libraries for package ?integer-gmp? Or were you referring to some other flag? Thanks! Ranjit. On Wed, Jun 10, 2015 at 9:41 PM, Carter Schonwald < carter.schonwald at gmail.com> wrote: > why were you trying to build profiling dylibs? i thought we only support > static linked profiling libs? (i could be wrong though) > > On Wed, Jun 10, 2015 at 9:26 AM, Ranjit Jhala wrote: > >> ah, my bad I thought I'd included that -- this is ghc 7.8.3, on MacOS, >> installed from https://ghcformacosx.github.io ... >> >> Should I just move to 7.10? >> >> On Wed, Jun 10, 2015 at 4:59 AM, Carter Schonwald < >> carter.schonwald at gmail.com> wrote: >> >>> What ghc version and how was it built? >>> >>> >>> On Wednesday, June 10, 2015, Ranjit Jhala wrote: >>> >>>> Hi all, >>>> >>>> I cannot build 'vector' (or 'cmdargs') with profiling on. >>>> >>>> specifically when I run: >>>> >>>> $ cabal install --enable-executable-profiling >>>> --enable-library-profiling --ghc-options="-O2 -rtsopts -prof -auto-all >>>> -caf-all" vector >>>> >>>> >>>> I get the message: >>>> >>>> Perhaps you haven't installed the "p_dyn" libraries for package >>>> ?integer-gmp? >>>> >>>> https://ghc.haskell.org/trac/ghc/ticket/8677 >>>> >>>> Per some advice I tried to add the '--disable-shared' >>>> >>>> >>>> $ cabal install --disable-shared --enable-executable-profiling >>>> --enable-library-profiling --ghc-options="-O2 -rtsopts -prof -auto-all >>>> -caf-all" vector >>>> >>>> but then I get this: >>>> >>>> Loading package primitive-0.6 ... : can't load >>>> .so/.DLL for: libHSprimitive-0.6.dylib (dlopen(libHSprimitive-0.6.dylib, >>>> 9): image not found) >>>> >>>> >>>> Any idea whats going on or for any work arounds? Pretty stumped! Thanks >>>> in advance! >>>> >>>> Ranjit. >>>> >>> >> >> >> -- >> Ranjit. >> > > -- Ranjit. -------------- next part -------------- An HTML attachment was scrubbed... URL: From carter.schonwald at gmail.com Thu Jun 11 13:07:39 2015 From: carter.schonwald at gmail.com (Carter Schonwald) Date: Thu, 11 Jun 2015 09:07:39 -0400 Subject: cannot build 'vector' with profiling In-Reply-To: References: Message-ID: Please share the exact way you're doing things. Vector does build fine as a static profiled lib on Mac, so the challege lies in understanding where your local configuration is broken. Please share more info. Or reinstall stuff On Jun 11, 2015 12:51 AM, "Ranjit Jhala" wrote: > ?Hi Carter, > > Are you referring to the '--disable-shared' flag? > > If so -- I added it because otherwise I got a bunch > of errors about: > > Perhaps you haven't installed the "p_dyn" > ? ? > libraries for package ?integer-gmp? > > Or were you referring to some other flag? > > Thanks! > > Ranjit. > > > > On Wed, Jun 10, 2015 at 9:41 PM, Carter Schonwald < > carter.schonwald at gmail.com> wrote: > >> why were you trying to build profiling dylibs? i thought we only support >> static linked profiling libs? (i could be wrong though) >> >> On Wed, Jun 10, 2015 at 9:26 AM, Ranjit Jhala wrote: >> >>> ah, my bad I thought I'd included that -- this is ghc 7.8.3, on MacOS, >>> installed from https://ghcformacosx.github.io ... >>> >>> Should I just move to 7.10? >>> >>> On Wed, Jun 10, 2015 at 4:59 AM, Carter Schonwald < >>> carter.schonwald at gmail.com> wrote: >>> >>>> What ghc version and how was it built? >>>> >>>> >>>> On Wednesday, June 10, 2015, Ranjit Jhala wrote: >>>> >>>>> Hi all, >>>>> >>>>> I cannot build 'vector' (or 'cmdargs') with profiling on. >>>>> >>>>> specifically when I run: >>>>> >>>>> $ cabal install --enable-executable-profiling >>>>> --enable-library-profiling --ghc-options="-O2 -rtsopts -prof -auto-all >>>>> -caf-all" vector >>>>> >>>>> >>>>> I get the message: >>>>> >>>>> Perhaps you haven't installed the "p_dyn" libraries for package >>>>> ?integer-gmp? >>>>> >>>>> https://ghc.haskell.org/trac/ghc/ticket/8677 >>>>> >>>>> Per some advice I tried to add the '--disable-shared' >>>>> >>>>> >>>>> $ cabal install --disable-shared --enable-executable-profiling >>>>> --enable-library-profiling --ghc-options="-O2 -rtsopts -prof -auto-all >>>>> -caf-all" vector >>>>> >>>>> but then I get this: >>>>> >>>>> Loading package primitive-0.6 ... : can't load >>>>> .so/.DLL for: libHSprimitive-0.6.dylib (dlopen(libHSprimitive-0.6.dylib, >>>>> 9): image not found) >>>>> >>>>> >>>>> Any idea whats going on or for any work arounds? Pretty stumped! >>>>> Thanks in advance! >>>>> >>>>> Ranjit. >>>>> >>>> >>> >>> >>> -- >>> Ranjit. >>> >> >> > > > -- > Ranjit. > -------------- next part -------------- An HTML attachment was scrubbed... URL: From jhala at cs.ucsd.edu Thu Jun 11 15:12:57 2015 From: jhala at cs.ucsd.edu (Ranjit Jhala) Date: Thu, 11 Jun 2015 08:12:57 -0700 Subject: cannot build 'vector' with profiling In-Reply-To: References: Message-ID: Hi Carter, OK, here's the full info (see log below), this is on an MBP, running ghc 7.8.3 (From ghcformac). In a new directory, I create a FRESH cabal sandbox, and then do: $ cabal install --enable-library-profiling --ghc-options="-O2 -rtsopts -prof -auto-all -caf-all" vector In doing so I get errors about unable to build 'primitive' because Failed to load interface for ?GHC.Integer.Type? Perhaps you haven't installed the "p_dyn" libraries for package ?integer-gmp?? Use -v to see a list of the files searched for. Googling the above takes me to https://ghc.haskell.org/trac/ghc/ticket/8677 But unfortunately I can't from the above tell exactly how to proceed. 1. Can you tell me how to get a profiling version of vector built in a new sandbox? i.e. what options are you using? 2. Is there any other information you need? I'm assuming since its in a sandbox I needn't nuke my global cabal directory but happy to if needed. Thanks! (log below) -- Ranjit. rjhala at borscht ~/r/l/tmp> mkdir vector-build rjhala at borscht ~/r/l/tmp> cd vector-build/ rjhala at borscht ~/r/l/t/vector-build> cabal sandbox init Writing a default package environment file to /Users/rjhala/research/liquid/tmp/vector-build/cabal.sandbox.config Creating a new sandbox at /Users/rjhala/research/liquid/tmp/vector-build/.cabal-sandbox rjhala at borscht ~/r/l/t/vector-build> cabal install --enable-library-profiling --ghc-options="-O2 -rtsopts -prof -auto-all -caf-all" vector Resolving dependencies... Notice: installing into a sandbox located at /Users/rjhala/research/liquid/tmp/vector-build/.cabal-sandbox Configuring primitive-0.6... Building primitive-0.6... Failed to install primitive-0.6 Last 10 lines of the build log ( /Users/rjhala/research/liquid/tmp/vector-build/.cabal-sandbox/logs/primitive-0.6.log ): Configuring primitive-0.6... Building primitive-0.6... Preprocessing library primitive-0.6... [ 1 of 10] Compiling Data.Primitive.Internal.Compat ( Data/Primitive/Internal/Compat.hs, dist/dist-sandbox-34ea82/build/Data/Primitive/Internal/Compat.o ) Top level: Failed to load interface for ?GHC.Integer.Type? Perhaps you haven't installed the "p_dyn" libraries for package ?integer-gmp?? Use -v to see a list of the files searched for. cabal: Error: some packages failed to install: primitive-0.6 failed during the building phase. The exception was: ExitFailure 1 vector-0.10.12.3 depends on primitive-0.6 which failed to install. rjhala at borscht ~/r/l/t/vector-build [1]> which ghc /Applications/ghc-7.8.3.app/Contents/bin/ghc -------------- next part -------------- An HTML attachment was scrubbed... URL: From carter.schonwald at gmail.com Thu Jun 11 15:32:26 2015 From: carter.schonwald at gmail.com (Carter Schonwald) Date: Thu, 11 Jun 2015 11:32:26 -0400 Subject: cannot build 'vector' with profiling In-Reply-To: References: Message-ID: Remove the prof flag and it will work. GHC is trying to do dylib with profiling On Jun 11, 2015 11:12 AM, "Ranjit Jhala" wrote: > Hi Carter, > > OK, here's the full info (see log below), this is on an MBP, > running ghc 7.8.3 (From ghcformac). > > In a new directory, I create a FRESH cabal sandbox, and then do: > > $ cabal install --enable-library-profiling --ghc-options="-O2 -rtsopts > -prof -auto-all -caf-all" vector > > In doing so I get errors about unable to build 'primitive' because > > Failed to load interface for ?GHC.Integer.Type? > Perhaps you haven't installed the "p_dyn" libraries for package > ?integer-gmp?? > Use -v to see a list of the files searched for. > > Googling the above takes me to > > https://ghc.haskell.org/trac/ghc/ticket/8677 > > But unfortunately I can't from the above tell exactly how to proceed. > > 1. Can you tell me how to get a profiling version of vector built in > a new sandbox? i.e. what options are you using? > > 2. Is there any other information you need? I'm assuming since its in > a sandbox I needn't nuke my global cabal directory but happy to if > needed. > > Thanks! (log below) > > -- Ranjit. > > rjhala at borscht ~/r/l/tmp> mkdir vector-build > rjhala at borscht ~/r/l/tmp> cd vector-build/ > rjhala at borscht ~/r/l/t/vector-build> cabal sandbox init > Writing a default package environment file to > /Users/rjhala/research/liquid/tmp/vector-build/cabal.sandbox.config > Creating a new sandbox at > /Users/rjhala/research/liquid/tmp/vector-build/.cabal-sandbox > rjhala at borscht ~/r/l/t/vector-build> cabal install > --enable-library-profiling --ghc-options="-O2 -rtsopts -prof -auto-all > -caf-all" vector > Resolving dependencies... > Notice: installing into a sandbox located at > /Users/rjhala/research/liquid/tmp/vector-build/.cabal-sandbox > Configuring primitive-0.6... > Building primitive-0.6... > Failed to install primitive-0.6 > Last 10 lines of the build log ( > /Users/rjhala/research/liquid/tmp/vector-build/.cabal-sandbox/logs/primitive-0.6.log > ): > Configuring primitive-0.6... > Building primitive-0.6... > Preprocessing library primitive-0.6... > [ 1 of 10] Compiling Data.Primitive.Internal.Compat ( > Data/Primitive/Internal/Compat.hs, > dist/dist-sandbox-34ea82/build/Data/Primitive/Internal/Compat.o ) > > Top level: > Failed to load interface for ?GHC.Integer.Type? > Perhaps you haven't installed the "p_dyn" libraries for package > ?integer-gmp?? > Use -v to see a list of the files searched for. > cabal: Error: some packages failed to install: > primitive-0.6 failed during the building phase. The exception was: > ExitFailure 1 > vector-0.10.12.3 depends on primitive-0.6 which failed to install. > rjhala at borscht ~/r/l/t/vector-build [1]> which ghc > /Applications/ghc-7.8.3.app/Contents/bin/ghc > > > > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From rwbarton at gmail.com Thu Jun 11 15:42:35 2015 From: rwbarton at gmail.com (Reid Barton) Date: Thu, 11 Jun 2015 11:42:35 -0400 Subject: cannot build 'vector' with profiling In-Reply-To: References: Message-ID: On Wed, Jun 10, 2015 at 12:18 AM, Ranjit Jhala wrote: > Hi all, > > I cannot build 'vector' (or 'cmdargs') with profiling on. > The short answer is: Never use --ghc-options="-prof". Cabal knows to use -prof to build profiling libraries and profiled executables, and will handle everything correctly automatically. If you remove the "-prof" part from the --ghc-options in your original command, vector will build with profiling correctly. The longer explanation is: vector uses Template Haskell which can only load the dynamic, unprofiled version of a library. In order to build vector in any configuration, its dependencies therefore need to have been built in at least the dynamic & unprofiled configuration. vector itself must also be built in the dynamic & unprofiled configuration, in case one module in vector runs a Template Haskell containing identifiers defined in another module in vector. Cabal is capable of building both the dynamic & unprofiled and static & profiled configurations of vector and its dependencies simultaneously by default. However, if you explicitly add --ghc-options=-prof, then you defeat Cabal's attempt to build the dynamic & unprofiled configuration. > specifically when I run: > > $ cabal install --enable-executable-profiling > --enable-library-profiling --ghc-options="-O2 -rtsopts -prof -auto-all > -caf-all" vector > > > I get the message: > > Perhaps you haven't installed the "p_dyn" libraries for package > ?integer-gmp? > Right, by default ghc does not ship with dynamic & profiled libraries, so this will fail very quickly when Cabal tries to build a dynamic & unprofiled library, but you told it to also pass -prof to ghc. > Per some advice I tried to add the '--disable-shared' > > > $ cabal install --disable-shared --enable-executable-profiling > --enable-library-profiling --ghc-options="-O2 -rtsopts -prof -auto-all > -caf-all" vector > > but then I get this: > > Loading package primitive-0.6 ... : can't load .so/.DLL > for: libHSprimitive-0.6.dylib (dlopen(libHSprimitive-0.6.dylib, 9): image > not found) > This can't work because you need dynamic versions of vector's dependencies for Template Haskell, but you disabled building them with --disable-shared. Regards, Reid Barton -------------- next part -------------- An HTML attachment was scrubbed... URL: From jhala at cs.ucsd.edu Thu Jun 11 15:46:25 2015 From: jhala at cs.ucsd.edu (Ranjit Jhala) Date: Thu, 11 Jun 2015 08:46:25 -0700 Subject: cannot build 'vector' with profiling In-Reply-To: References: Message-ID: Thanks Carter and Reid! (I suspect I'd copied those options from somewhere a long time ago when they worked...) Things seem to be building now! Thanks a bunch!? -------------- next part -------------- An HTML attachment was scrubbed... URL: From simonpj at microsoft.com Thu Jun 11 16:21:49 2015 From: simonpj at microsoft.com (Simon Peyton Jones) Date: Thu, 11 Jun 2015 16:21:49 +0000 Subject: 7.10 branch Message-ID: <1ad5042fb0d54d718443ec9a35066b48@DB4PR30MB030.064d.mgd.msft.net> Austin I'm getting these validation failures on the 7.10 branch. Are you? This is on Linux. Simon Unexpected failures: driver T8959a [bad stderr] (normal) ghci/scripts T9878b [bad stderr] (ghci) th T10279 [stderr mismatch] (normal) Unexpected stat failures: perf/should_run T4830 [stat not good enough] (normal) perf/should_run T7436 [stat not good enough] (normal) -------------- next part -------------- An HTML attachment was scrubbed... URL: From carter.schonwald at gmail.com Thu Jun 11 22:52:13 2015 From: carter.schonwald at gmail.com (Carter Schonwald) Date: Thu, 11 Jun 2015 18:52:13 -0400 Subject: cannot build 'vector' with profiling In-Reply-To: References: Message-ID: I just always set profiling to True in ~/.cabal/config and then call it a day :) I believe cabal or something has a notion of profiling ghc options that are only supplied when building profiling libs, but I don't remember precisely where they are or if they are a thing On Thursday, June 11, 2015, Ranjit Jhala wrote: > Thanks Carter and Reid! (I suspect I'd copied those options from somewhere > a long time ago when they worked...) Things seem to be building now! Thanks > a bunch!? > -------------- next part -------------- An HTML attachment was scrubbed... URL: From simonpj at microsoft.com Sat Jun 13 23:07:30 2015 From: simonpj at microsoft.com (Simon Peyton Jones) Date: Sat, 13 Jun 2015 23:07:30 +0000 Subject: overlapping instances in 7.10.1 In-Reply-To: <1432415282.2467.15.camel@one.mechvel.pereslavl.ru> References: <1432415282.2467.15.camel@one.mechvel.pereslavl.ru> Message-ID: <3b6fd5fd8dbc4414af8d8e1f3aaae67c@DB4PR30MB030.064d.mgd.msft.net> Sergei I finally found time to look into what is happening here. It's a good illustration of the dangers of overlapping instances. Here is the setup: * Module ResEuc_ * Contains instance (...) => Ring (ResidueE a) <---- (A) instance (..., Ring (ResidueE a)) => Field (ResidueE a) <---- (B) * Module PFact__ * Imports Pgcd_, which imports ResEuc_ * Contains code that needs (Field (ResidueE (UPol (ResidueE Integer)))) <------ (X) * To solve (X) we use instance (B) from ResEuc_ * And hence we need to solve (Ring (ResidueE (UPol (ResidueE Integer)))) which we do using (A) but not (C) * Module RsePol_ * Imports PFact__ * Contains the specialised instance instance (...) => Ring (ResidueE (UPol a)) <------ (C) which overlaps instance (A) * Module Main * Needs an instance for Field (ResidueE (UPol (Residue Integer))) <------ (Y) * Although GHC *could* generate this by instance declarations, which it would do using (B) and then using (C), instead GHC cleverly sees that it has generated it before, in module PFact__, and so uses the one from PFact__. And that is what gives rise to your error So the real problem is that in PFact__, we make an instance (X) that does not see the specialised instance (C). It *cannot* see that instance because RsePol_ imports PFact__. So whatever code uses (X) is not going to see the specialised instance. I bet that this is not what you intend. This may be a latent bug in DoCon. I solved the problem by combining PFact__ and RsePol_ into a single module. Then everything works fine. What are the general lessons here? * GHC generally assumes that if it generates (C T) in one place, then it can use that anywhere in the program that (C T) is needed. That is, there is only one (C T) dictionary. * But suppose you have overlapping instance in different modules; say module A where instance C [a] module B where import A; instance C [Maybe a] If you use (C [Maybe Int]) in A, then of course we won't see the instance in B. So you'll get a different dictionary than if you compute C [Maybe Int] in module B. In short, overlapping instances are OK, but it's best to put them in the same module as the instances they overlap. Could GHC behave as if all instances were calculated afresh in the module being compiled. Yes, of course it could, but at the cost of losing the benefit of cross-module specialisation. An overloaded function specialised at, say, [Int] in one module could not be re-used in another in case the instances changed. Simon | -----Original Message----- | From: ghc-tickets [mailto:ghc-tickets-bounces at haskell.org] On Behalf Of | Sergei Meshveliani | Sent: 23 May 2015 22:08 | To: glasgow-haskell-users at haskell.org | Cc: glasgow-haskell-bugs at haskell.org | Subject: overlapping instances in 7.10.1 | | Dear GHC developers, | | This request overrides my previous one of "7.10.1-err..." | (it is simpler and more precise). | The archive | | http://www.botik.ru/pub/local/Mechveliani/ghcQuest/7.10.1-errReport- | may23-2015.zip | | presents a question about ghc-7.10.1. | | Make it, please, with ghc-7.10.1 by | | ghc $doconCpOpt -O --make Main | , | $doconCpOpt = | -fwarn-unused-matches -fwarn-unused-binds -fwarn-unused-imports | -fno-warn-overlapping-patterns -XRecordWildCards -XNamedFieldPuns | -XFlexibleContexts -XMultiParamTypeClasses -XUndecidableInstances | -XTypeSynonymInstances -XFlexibleInstances -fcontext-stack=30 | | | as it is written there in README.txt. | | README.txt explains which two instances are wrongly resolved | -- as I expect. | | In ghc-7.8.2 they are resolved in a correct way | (and there is a different pragma syntax). | I conclude this from running the test in docon-2.12. | | Am I missing something? | | Please, advise, | | ------ | Sergei | | | | | _______________________________________________ | ghc-tickets mailing list | ghc-tickets at haskell.org | http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-tickets -------------- next part -------------- An HTML attachment was scrubbed... URL: From mechvel at botik.ru Sun Jun 14 15:56:20 2015 From: mechvel at botik.ru (Sergei Meshveliani) Date: Sun, 14 Jun 2015 19:56:20 +0400 Subject: overlapping instances in 7.10.1 In-Reply-To: <3b6fd5fd8dbc4414af8d8e1f3aaae67c@DB4PR30MB030.064d.mgd.msft.net> References: <1432415282.2467.15.camel@one.mechvel.pereslavl.ru> <3b6fd5fd8dbc4414af8d8e1f3aaae67c@DB4PR30MB030.064d.mgd.msft.net> Message-ID: <1434297380.2343.33.camel@one.mechvel.pereslavl.ru> On Sat, 2015-06-13 at 23:07 +0000, Simon Peyton Jones wrote: (I reformat this text a bit) > [..] > I finally found time to look into what is happening here. It?s a good > illustration of the dangers of overlapping instances. Here is the > setup: > > > * Module ResEuc_ > > * Contains > instance (...) => Ring (ResidueE a) <---- (A) > instance (..., Ring (ResidueE a)) => Field (ResidueE a) <---- (B) > > > * Module PFact__ > > * Imports Pgcd_, which imports ResEuc_ > > * Contains code that needs > > (Field (ResidueE (UPol (ResidueE Integer)))) <------ (X) > > * To solve (X) we use instance (B) from ResEuc_ > * And hence we need to solve > (Ring (ResidueE (UPol (ResidueE Integer)))) > > which we do using (A) but not (C) > > > * Module RsePol_ > > * Imports PFact__ > * Contains the specialised instance > > instance (...) => Ring (ResidueE (UPol a)) <------ (C) > > which overlaps instance (A) > > * Module Main > * Needs an instance for > > Field (ResidueE (UPol (Residue Integer))) <------ (Y) > > * Although GHC *could* generate this by instance declarations, > which it would do using (B) and then using (C), > > instead GHC cleverly sees that it has generated it before, > in module PFact__, and so uses the one from PFact__. > And that is what gives rise to your error > > > So the real problem is that in PFact__, we make an instance (X) that > does not see the specialised instance (C). > It *cannot* see that instance because RsePol_ imports PFact__. (is is called Pfact__). Yes, I intended this. And this is not a problem. This is because Pfact_ uses somewhat a smaller knowledge library than there may use further modules which import Pfact_. > So whatever code uses (X) is not going to see the specialised > instance. Why? ghc-7.8.3 treats overlapping instances differently. My intention was (and is) as follows. Compiling Main, the compiler sees the two solutions for (Y): the one imported from Pfact__ -- which implementation (dictionary?) is ready, and another that can be generated using (C) from RsePol_. By the meaning of what are overlapping instances, the compiler must resolve between these two. And this is resolved by the rule of checking the substitutional instance between instances. `Main' imports more knowledge about instances than Pfact_ does, so it is supposed to use an additional knowledge. The fact that one of the overlapping instances is already generated must not be a sufficient reason to set it in Main. This is why I think that ghc-7.8.3 treats the OI notion in a more natural way than ghc-7.10.1 does. May be, ghc-7.10.1 has a better technical tool for this, but ghc-7.8.3 corresponds to a natural notion of OI. Can GHC return to a natural OI notion? Or am I missing something? > I bet that this is not what you intend. This may be a latent bug in > DoCon. If I am not missing anything in my above discourse, then DoCon is all right at this point. > I solved the problem by combining PFact__ and RsePol_ into a single > module. Then everything works fine. I think that this approach will generally lead to great difficulties in composing an application. Please, consider my above explanation and tell me whether I am missing something. Regards, ------ Sergei > What are the general lessons here? > > GHC generally assumes that if it generates (C T) in one place, > then it can use that anywhere in the program that (C T) is needed. > That is, there is only one (C T) dictionary. > > > ? But suppose you have overlapping instance in different > modules; say > > module A where instance C [a] > > module B where import A; instance C [Maybe a] > > If you use (C [Maybe Int]) in A, then of course we won?t see the > instance in B. So you?ll get a different dictionary than if you > compute C [Maybe Int] in module B. > > > > In short, overlapping instances are OK, but it?s best to put them in > the same module as the instances they overlap. > > > > Could GHC behave as if all instances were calculated afresh in the > module being compiled. Yes, of course it could, but at the cost of > losing the benefit of cross-module specialisation. An overloaded > function specialised at, say, [Int] in one module could not be re-used > in another in case the instances changed. > > > > Simon > > > | -----Original Message----- > | From: ghc-tickets [mailto:ghc-tickets-bounces at haskell.org] On Behalf > Of > | Sergei Meshveliani > | Sent: 23 May 2015 22:08 > | To: glasgow-haskell-users at haskell.org > | Cc: glasgow-haskell-bugs at haskell.org > | Subject: overlapping instances in 7.10.1 > | Dear GHC developers, > | > | This request overrides my previous one of "7.10.1-err..." > | (it is simpler and more precise). > | The archive > | http://www.botik.ru/pub/local/Mechveliani/ghcQuest/7.10.1-errReport- > | may23-2015.zip > | > | presents a question about ghc-7.10.1. > > | Make it, please, with ghc-7.10.1 by > | ghc $doconCpOpt -O --make Main > | , > | $doconCpOpt = > | -fwarn-unused-matches -fwarn-unused-binds -fwarn-unused-imports > | -fno-warn-overlapping-patterns -XRecordWildCards -XNamedFieldPuns > | -XFlexibleContexts -XMultiParamTypeClasses -XUndecidableInstances > | -XTypeSynonymInstances -XFlexibleInstances -fcontext-stack=30 > > | > | as it is written there in README.txt. > | README.txt explains which two instances are wrongly resolved > | -- as I expect. > | In ghc-7.8.2 they are resolved in a correct way > | (and there is a different pragma syntax). > | I conclude this from running the test in docon-2.12. > | Am I missing something? > | Please, advise, > | ------ > | Sergei From austin at well-typed.com Mon Jun 15 00:16:09 2015 From: austin at well-typed.com (Austin Seipp) Date: Sun, 14 Jun 2015 19:16:09 -0500 Subject: ANNOUNCE: GHC 7.10.2 Release Candidate 1 Message-ID: We are pleased to announce the first release candidate for GHC 7.10.2: https://downloads.haskell.org/~ghc/7.10.2-rc1 https://downloads.haskell.org/~ghc/7.10.2-rc1/docs/html/ This includes the source tarball and bindists for Windows, Mac OS X, and Debian Linux. FreeBSD and Solaris binaries will follow soon. These binaries and tarballs have an accompanying SHA256SUMS file signed by my GPG key id (0x3B58D86F). We plan to make the 7.10.2 final release at the end of this coming week - so please test as much as possible; bugs are much cheaper if we find them before the release! -- Regards, Austin Seipp, Haskell Consultant Well-Typed LLP, http://www.well-typed.com/ From austin at well-typed.com Sun Jun 14 23:34:14 2015 From: austin at well-typed.com (Austin Seipp) Date: Sun, 14 Jun 2015 18:34:14 -0500 Subject: ANNOUNCE: GHC 7.10.2 Release Candidate 1 Message-ID: We are pleased to announce the first release candidate for GHC 7.10.2: https://downloads.haskell.org/~ghc/7.10.2-rc1 https://downloads.haskell.org/~ghc/7.10.2-rc1/docs/html/ This includes the source tarball and bindists for Windows, Mac OS X, and Debian Linux. FreeBSD and Solaris binaries will follow soon. These binaries and tarballs have an accompanying SHA256SUMS file signed by my GPG key id (0x3B58D86F). We plan to make the 7.10.2 final release at the end of this coming week - so please test as much as possible; bugs are much cheaper if we find them before the release! -- Regards, Austin Seipp, Haskell Consultant Well-Typed LLP, http://www.well-typed.com/ From asr at eafit.edu.co Mon Jun 15 03:25:57 2015 From: asr at eafit.edu.co (=?UTF-8?B?QW5kcsOpcyBTaWNhcmQtUmFtw61yZXo=?=) Date: Sun, 14 Jun 2015 22:25:57 -0500 Subject: ANNOUNCE: GHC 7.10.2 Release Candidate 1 In-Reply-To: References: Message-ID: On 14 June 2015 at 19:16, Austin Seipp wrote: > We are pleased to announce the first release candidate for GHC 7.10.2: Since transformers is a GHC-include library, is there any particular reason why GHC 7.10.2 RC1 didn't include the latest version of the transformers library, i.e. transformers-0.4.3.0? -- Andr?s From robertce at cse.unsw.edu.au Mon Jun 15 04:18:48 2015 From: robertce at cse.unsw.edu.au (Rob Everest) Date: Mon, 15 Jun 2015 04:18:48 +0000 Subject: ANNOUNCE: GHC 7.10.2 Release Candidate 1 In-Reply-To: References: Message-ID: > > We plan to make the 7.10.2 final release at the end of this coming week - > so please test as much as possible; bugs are much cheaper if we find them > before the release! Could I possibly draw attention to #10491 ? It's a regression in the simplifier that is causing considerable pain for Accelerate, namely a compile time of many hours for a 300 line module. It would be unfortunate if this couldn't be resolved for the 7.10.2 release. -------------- next part -------------- An HTML attachment was scrubbed... URL: From simonpj at microsoft.com Mon Jun 15 09:29:30 2015 From: simonpj at microsoft.com (Simon Peyton Jones) Date: Mon, 15 Jun 2015 09:29:30 +0000 Subject: overlapping instances in 7.10.1 In-Reply-To: <1434297380.2343.33.camel@one.mechvel.pereslavl.ru> References: <1432415282.2467.15.camel@one.mechvel.pereslavl.ru> <3b6fd5fd8dbc4414af8d8e1f3aaae67c@DB4PR30MB030.064d.mgd.msft.net> <1434297380.2343.33.camel@one.mechvel.pereslavl.ru> Message-ID: <46b2c9887b88499e8f52fe6a05569277@DB4PR30MB030.064d.mgd.msft.net> | This is why I think that ghc-7.8.3 treats the OI notion in a more | natural way than ghc-7.10.1 does. | May be, ghc-7.10.1 has a better technical tool for this, but ghc- | 7.8.3 corresponds to a natural notion of OI. | | Can GHC return to a natural OI notion? | Or am I missing something? Well it all depends what you mean by "natural". To me it is profoundly un-natural to deliberately have the same type-class constraint solved in two different ways in the same program! To require this would prevent cross-module specialisation. If I have f :: C a => a -> a in one module, and I specialise it to f_spec :: [Int] -> [Int] in one module, I want to be free to re-use that specialisation in other modules. But under your "natural" story, I cannot do that, because (C [Int]) might be resolved differently there. I'd be interested in what others think. I've started https://ghc.haskell.org/trac/ghc/ticket/10526 to collect these points. Meanwhile, Sergei, it's clear how to fix docon, so you are no longer stuck. Simon | | | | > I bet that this is not what you intend. This may be a latent bug | in | > DoCon. | | If I am not missing anything in my above discourse, then DoCon is all | right at this point. | | | > I solved the problem by combining PFact__ and RsePol_ into a single | > module. Then everything works fine. | | I think that this approach will generally lead to great difficulties | in | composing an application. | | Please, consider my above explanation and tell me whether I am missing | something. | | Regards, | | ------ | Sergei | | | | > What are the general lessons here? | > | > GHC generally assumes that if it generates (C T) in one | place, | > then it can use that anywhere in the program that (C T) is needed. | > That is, there is only one (C T) dictionary. | > | > | > ? But suppose you have overlapping instance in different | > modules; say | > | > module A where instance C [a] | > | > module B where import A; instance C [Maybe a] | > | > If you use (C [Maybe Int]) in A, then of course we won?t see the | > instance in B. So you?ll get a different dictionary than if you | > compute C [Maybe Int] in module B. | > | > | > | > In short, overlapping instances are OK, but it?s best to put them in | > the same module as the instances they overlap. | > | > | > | > Could GHC behave as if all instances were calculated afresh in the | > module being compiled. Yes, of course it could, but at the cost of | > losing the benefit of cross-module specialisation. An overloaded | > function specialised at, say, [Int] in one module could not be re- | used | > in another in case the instances changed. | > | > | > | > Simon | > | > | | > | -----Original Message----- | > | From: ghc-tickets [mailto:ghc-tickets-bounces at haskell.org] On | Behalf | > Of | > | Sergei Meshveliani | > | Sent: 23 May 2015 22:08 | > | To: glasgow-haskell-users at haskell.org | > | Cc: glasgow-haskell-bugs at haskell.org | > | Subject: overlapping instances in 7.10.1 | | > | Dear GHC developers, | > | | > | This request overrides my previous one of "7.10.1-err..." | > | (it is simpler and more precise). | > | The archive | | > | http://www.botik.ru/pub/local/Mechveliani/ghcQuest/7.10.1- | errReport- | > | may23-2015.zip | > | | > | presents a question about ghc-7.10.1. | > | > | Make it, please, with ghc-7.10.1 by | | > | ghc $doconCpOpt -O --make Main | > | , | > | $doconCpOpt = | | > | -fwarn-unused-matches -fwarn-unused-binds -fwarn-unused-imports | > | -fno-warn-overlapping-patterns -XRecordWildCards -XNamedFieldPuns | > | -XFlexibleContexts -XMultiParamTypeClasses -XUndecidableInstances | > | -XTypeSynonymInstances -XFlexibleInstances -fcontext-stack=30 | > | > | | > | as it is written there in README.txt. | > | README.txt explains which two instances are wrongly resolved | > | -- as I expect. | | > | In ghc-7.8.2 they are resolved in a correct way | > | (and there is a different pragma syntax). | > | I conclude this from running the test in docon-2.12. | | > | Am I missing something? | > | Please, advise, | | > | ------ | > | Sergei | From mechvel at botik.ru Mon Jun 15 12:25:44 2015 From: mechvel at botik.ru (Sergei Meshveliani) Date: Mon, 15 Jun 2015 16:25:44 +0400 Subject: overlapping instances in 7.10.1 In-Reply-To: <46b2c9887b88499e8f52fe6a05569277@DB4PR30MB030.064d.mgd.msft.net> References: <1432415282.2467.15.camel@one.mechvel.pereslavl.ru> <3b6fd5fd8dbc4414af8d8e1f3aaae67c@DB4PR30MB030.064d.mgd.msft.net> <1434297380.2343.33.camel@one.mechvel.pereslavl.ru> <46b2c9887b88499e8f52fe6a05569277@DB4PR30MB030.064d.mgd.msft.net> Message-ID: <1434371144.4718.18.camel@one.mechvel.pereslavl.ru> On Mon, 2015-06-15 at 09:29 +0000, Simon Peyton Jones wrote: > | This is why I think that ghc-7.8.3 treats the OI notion in a more > | natural way than ghc-7.10.1 does. > | May be, ghc-7.10.1 has a better technical tool for this, but ghc- > | 7.8.3 corresponds to a natural notion of OI. > | > | Can GHC return to a natural OI notion? > | Or am I missing something? > > Well it all depends what you mean by "natural". To me it is profoundly un-natural to deliberately have the same type-class constraint solved in two different ways in the same program! > > To require this would prevent cross-module specialisation. If I have > f :: C a => a -> a > in one module, and I specialise it to > f_spec :: [Int] -> [Int] > in one module, I want to be free to re-use that specialisation in other modules. But under your "natural" story, I cannot do that, because (C [Int]) might be resolved differently there. > > I'd be interested in what others think. I've started > https://ghc.haskell.org/trac/ghc/ticket/10526 > to collect these points. > > Meanwhile, Sergei, it's clear how to fix docon, so you are no longer stuck. I hope DoCon is not stuck -- because it relies (so far) on ghc-7.8.3. But I need to understand the subject of overlapping instances (OI). ---------- I am writing this _here_ because to clicking at https://ghc.haskell.org/trac/ghc/ticket/10526 my browser responds Problem occurred while loading the URL https://ghc.haskell.org/trac/ghc/ticket/10526 SSL handshake failed: A TLS fatal alert has been received. Then, I start searching from https://ghc.haskell.org/trac/ghc/ and cannot find #10526 Also I had earlier a certain difficulty with registering to this bug tracker, and suspect that registration was not fully successful, so that I doubt that I can write there. May I, please, discuss the subject here? ------------------- The report of 7.10.1-errReport-may23-2015.zip shows that 7.8.3 and 7.10.1 treat OI differently, But this report is rather complex. Instead consider the following simple example. -------------------------------------------- module A where class Size a where size :: a -> Int instance {-# OVERLAPPING #-} Size [a] where size = length f :: Size a => a -> Int f = size g :: [Maybe Int] -> Int g = size ---------------------------------------- module Main where import A instance {-# OVERLAPPING #-} Size [Maybe a] where size _ = -1 mbs = [] :: [Maybe Int] main = putStr (shows (f mbs) "\n") -- I -1 -- putStr (shows (g mbs) "\n") -- II 0 -------------------------------------------- Making and running in ghc-7.10.1 : ghc --make -XFlexibleInstances Main ./Main It prints "-1" for the line (I) for main, and "0" for the line (II). To compare to ghc-7.8.3, comment out the pragma and add -XOverlappingInstances to the ghc call. And this yields the same results -1 and -0 respectively. Please, how to change (a bit) the above simple example in order to see the difference between 7.8.3 and 7.10.1 ? Thanks, ------ Sergei From austin at well-typed.com Mon Jun 15 14:15:23 2015 From: austin at well-typed.com (Austin Seipp) Date: Mon, 15 Jun 2015 09:15:23 -0500 Subject: ANNOUNCE: GHC 7.10.2 Release Candidate 1 In-Reply-To: References: Message-ID: Yes, as noted on the ticket, I've bumped the priority and we'll be looking into this - and hopefully have a fix in time for 7.10.2. There are some similar tickets where we get large explosions of terms, so it may be in the same ballpark. On Sun, Jun 14, 2015 at 11:18 PM, Rob Everest wrote: >> We plan to make the 7.10.2 final release at the end of this coming week - >> so please test as much as possible; bugs are much cheaper if we find them >> before the release! > > > Could I possibly draw attention to #10491? It's a regression in the > simplifier that is causing considerable pain for Accelerate, namely a > compile time of many hours for a 300 line module. It would be unfortunate if > this couldn't be resolved for the 7.10.2 release. -- Regards, Austin Seipp, Haskell Consultant Well-Typed LLP, http://www.well-typed.com/ From austin at well-typed.com Mon Jun 15 14:19:36 2015 From: austin at well-typed.com (Austin Seipp) Date: Mon, 15 Jun 2015 09:19:36 -0500 Subject: ANNOUNCE: GHC 7.10.2 Release Candidate 1 In-Reply-To: References: Message-ID: Not in particular - I guess we didn't get everything we precisely needed for the RC. I've filed a ticket: #10530 On Sun, Jun 14, 2015 at 10:25 PM, Andr?s Sicard-Ram?rez wrote: > On 14 June 2015 at 19:16, Austin Seipp wrote: >> We are pleased to announce the first release candidate for GHC 7.10.2: > > Since transformers is a GHC-include library, is there any particular > reason why GHC 7.10.2 RC1 didn't include the latest version of the > transformers library, i.e. transformers-0.4.3.0? > > -- > Andr?s > -- Regards, Austin Seipp, Haskell Consultant Well-Typed LLP, http://www.well-typed.com/ From juhpetersen at gmail.com Mon Jun 15 14:35:51 2015 From: juhpetersen at gmail.com (Jens Petersen) Date: Mon, 15 Jun 2015 23:35:51 +0900 Subject: ANNOUNCE: GHC 7.10.2 Release Candidate 1 In-Reply-To: References: Message-ID: On 15 June 2015 at 09:16, Austin Seipp wrote: > We are pleased to announce the first release candidate for GHC 7.10.2: Thank you I did a 'quick' build of it for Fedora 22 in my Copr repo: https://copr.fedoraproject.org/coprs/petersen/ghc-7.10.2 I will try to update it to a 'perf' build soon. Cheers, Jens From mietek at bak.io Mon Jun 15 17:05:15 2015 From: mietek at bak.io (=?iso-8859-1?Q?Mi=EBtek_Bak?=) Date: Mon, 15 Jun 2015 18:05:15 +0100 Subject: ANNOUNCE: GHC 7.10.2 Release Candidate 1 In-Reply-To: References: Message-ID: Thanks. GHC 7.10.2-rc1 can now be installed with Halcyon: halcyon install --ghc-version=7.10.2-rc1 --cabal-version=1.22.4.0 Supported platforms include: - Amazon Linux 2014.09 - Arch Linux - CentOS 6, 7 - Debian 6, 7, 8 - Gentoo Linux - openSUSE 13.2 - OS X 10.8, 10.9, 10.10 - Red Hat Enterprise Linux 6, 7 - Slackware 14.1 - SUSE Linux Enterprise Server 12 - Ubuntu 12.04 LTS, 14.04 LTS, 14.10, 15.04 - Fedora 20, 21 -- Mi?tek https://mietek.io On 2015-06-15, at 01:16, Austin Seipp wrote: > We are pleased to announce the first release candidate for GHC 7.10.2: > > https://downloads.haskell.org/~ghc/7.10.2-rc1 > https://downloads.haskell.org/~ghc/7.10.2-rc1/docs/html/ > > This includes the source tarball and bindists for Windows, Mac OS X, > and Debian Linux. FreeBSD and Solaris binaries will follow soon. These > binaries and tarballs have an accompanying SHA256SUMS file signed by > my GPG key id (0x3B58D86F). > > We plan to make the 7.10.2 final release at the end of this coming > week - so please test as much as possible; bugs are much cheaper if we > find them before the release! > > -- > Regards, > > Austin Seipp, Haskell Consultant > Well-Typed LLP, http://www.well-typed.com/ > _______________________________________________ > ghc-devs mailing list > ghc-devs at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs -------------- next part -------------- A non-text attachment was scrubbed... Name: smime.p7s Type: application/pkcs7-signature Size: 4203 bytes Desc: not available URL: From mechvel at botik.ru Mon Jun 15 20:03:27 2015 From: mechvel at botik.ru (Sergei Meshveliani) Date: Tue, 16 Jun 2015 00:03:27 +0400 Subject: overlapping instances in 7.10.1 In-Reply-To: <46b2c9887b88499e8f52fe6a05569277@DB4PR30MB030.064d.mgd.msft.net> References: <1432415282.2467.15.camel@one.mechvel.pereslavl.ru> <3b6fd5fd8dbc4414af8d8e1f3aaae67c@DB4PR30MB030.064d.mgd.msft.net> <1434297380.2343.33.camel@one.mechvel.pereslavl.ru> <46b2c9887b88499e8f52fe6a05569277@DB4PR30MB030.064d.mgd.msft.net> Message-ID: <1434398607.3093.109.camel@one.mechvel.pereslavl.ru> On Mon, 2015-06-15 at 09:29 +0000, Simon Peyton Jones wrote: > | This is why I think that ghc-7.8.3 treats the OI notion in a more > | natural way than ghc-7.10.1 does. > | May be, ghc-7.10.1 has a better technical tool for this, but ghc- > | 7.8.3 corresponds to a natural notion of OI. > | > | Can GHC return to a natural OI notion? > | Or am I missing something? > > Well it all depends what you mean by "natural". To me it is profoundly > un-natural to deliberately have the same type-class constraint solved in > two different ways in the same program! > > To require this would prevent cross-module specialisation. If I have > f :: C a => a -> a > in one module, and I specialise it to > f_spec :: [Int] -> [Int] > in one module, I want to be free to re-use that specialisation in other modules. > But under your "natural" story, I cannot do that, because (C [Int]) might be > resolved differently there. Now, I give a simple (and a very contrived) example illustrating of how overlapping instances (OI) are used in DoCon. Also this example is made after the sample that Simon has given in his recent letter: > GHC generally assumes that if it generates (the instance) > (C T) in one place, then it can use that anywhere in the program that > (C T) is needed. That is, there is only one (C T) dictionary. > > But suppose you have overlapping instance in different modules; say > > module A where instance C [a] > module B where import A; instance C [Maybe a] > > If you use (C [Maybe Int]) in A, then of course we won?t see the > instance in B. So you?ll get a different dictionary than if you > compute C [Maybe Int] in module B. > > In short, overlapping instances are OK, but it?s best to put them in > the same module as the instances they overlap. My example: ------------------------------------------------------------ module A where class Att a where att :: a -> (Int , Maybe Int) instance {-# OVERLAPPING #-} Att [a] where att xs = (length (reverse xs) , Nothing) f :: [Maybe Int] -> (Int , Maybe Int) f = att ----------------- module Main where import A instance {-# OVERLAPPING #-} Att [Maybe a] where att mbs = (length mbs , Just 1) mbs = [] :: [Maybe Int] main = putStr (shows (f mbs) "\n") -- (I) (0 , Nothing) -- putStr (shows (att mbs) "\n") -- (II) (0, Just 1) ---------------------------------------------------------------------- Att stands for the class C of Simon's letter. It means "certain attributes of a value, and also of its type". The value Nothing for the second part of (att a) means that the second component of attributes is not definitely known for this particular instance. length (reverse xs) imitates a non-optimal method for computing att in the instance for a => [a]. This instance is very general, so that the first component of attributes is evaluated in-efficiently (but correct), the second component has a correct value, but highly indefinite (few information derived). The function f uses the instance Att [Maybe Int], and it is satisfied with the generic instance given in A.hs. Because a) at this stage of the project there is not enough functionality to implement a better special method b) for this particular case in this module the generic instance is sufficient. Main.hs defines a special instance of Att for [Maybe a]. This instance in more special than the one defined in A.hs. And the value (att mbs) has the first component evaluated more efficiently than for the generic (Att [a]) instance. But the value is the same. The second component even has a different value in the result. But it is considered as correct (this is similar to the situation of: "generally the speed is 2 < s < 8, and in this the special case it is 3"). The call (att mbs) in `main' uses a different dictionary for Att than the call A.f (mbs). Right? Both ghc-7.8.3 (with -XFlexibleInstnce -XOverlappingInstances in the call) and ghc-7.10.1 (with -XFlexibleInstnce in the call) give the same results in 'main': (0, Nothing) for the line (I) and (0, Just 1) for the line (II). And I thought that everything is set naturally in this program. Simon, you would state that as A.f and (Main.att mbs) use the instances of Att for the same type [Maybe Int], "overlapping instances are OK, but it?s best to put them in the same module as the instances they overlap". I do not understand the grammar of the phrase in quotes, either it has a typo or this is too difficult English for me. Anyway: does this mean for this particular example, that it is highly desirable to set the two above instance declarations in the same module ? 1) What if they are in different modules, like in the above example. What unnatural may happen -- for example? 2) At least ghc-7.8.3 and ghc-7.10.1 do the same in this example. May be, you can change this example a bit to make ghc-7.8.3 and ghc-7.10.1 diverse, so that my example bug becomes visible? (they diverse on 7.10.1-errReport-may23-2015.zip but this bunch of modules is too complex). 3) It is not practical to join the above A.hs and Main.hs into one module. Because generally, between A.hs and Main.hs there are added many modules with much functionality, and the instance implementation in Main uses this functionality. This will be similar as putting all the developed library into one module. Please, advise, ------ Sergei From mechvel at botik.ru Tue Jun 16 11:51:25 2015 From: mechvel at botik.ru (Sergei Meshveliani) Date: Tue, 16 Jun 2015 14:51:25 +0300 Subject: overlapping instances in 7.10.1 In-Reply-To: <1434398607.3093.109.camel@one.mechvel.pereslavl.ru> References: <1432415282.2467.15.camel@one.mechvel.pereslavl.ru> <3b6fd5fd8dbc4414af8d8e1f3aaae67c@DB4PR30MB030.064d.mgd.msft.net> <1434297380.2343.33.camel@one.mechvel.pereslavl.ru> <46b2c9887b88499e8f52fe6a05569277@DB4PR30MB030.064d.mgd.msft.net> <1434398607.3093.109.camel@one.mechvel.pereslavl.ru> Message-ID: <1434455485.25782.10.camel@scico.botik.ru> On Tue, 2015-06-16 at 00:03 +0400, Sergei Meshveliani wrote: > [..] > 2) At least ghc-7.8.3 and ghc-7.10.1 do the same in this example. > May be, you can change this example a bit to make ghc-7.8.3 and > ghc-7.10.1 diverse, so that my example bug becomes visible? > (they diverse on 7.10.1-errReport-may23-2015.zip but this bunch > of modules is too complex). (this is in the end of my last letter). I am trying now to reduce the report of 7.10.1-errReport-may23-2015.zip into something simple. And discover that Main yields a different result for -Onot. Probably, DoCon-2.12.1 will run correct under -Onot. For me, this is not important, because -O is desirable anyway. But for the GHC developers this effect may present some information. Regards, ------ Sergei > On Mon, 2015-06-15 at 09:29 +0000, Simon Peyton Jones wrote: > > | This is why I think that ghc-7.8.3 treats the OI notion in a more > > | natural way than ghc-7.10.1 does. > > | May be, ghc-7.10.1 has a better technical tool for this, but ghc- > > | 7.8.3 corresponds to a natural notion of OI. > > | > > | Can GHC return to a natural OI notion? > > | Or am I missing something? > > > > Well it all depends what you mean by "natural". To me it is profoundly > > un-natural to deliberately have the same type-class constraint solved in > > two different ways in the same program! > > > > To require this would prevent cross-module specialisation. If I have > > f :: C a => a -> a > > in one module, and I specialise it to > > f_spec :: [Int] -> [Int] > > in one module, I want to be free to re-use that specialisation in other modules. > > But under your "natural" story, I cannot do that, because (C [Int]) might be > > resolved differently there. > > > Now, I give a simple (and a very contrived) example illustrating of how > overlapping instances (OI) > are used in DoCon. > Also this example is made after the sample that Simon has given in his > recent letter: > > [..] > 2) At least ghc-7.8.3 and ghc-7.10.1 do the same in this example. > May be, you can change this example a bit to make ghc-7.8.3 and > ghc-7.10.1 diverse, so that my example bug becomes visible? > (they diverse on 7.10.1-errReport-may23-2015.zip but this bunch of > modules is too complex). [..] From qdunkan at gmail.com Wed Jun 17 06:19:49 2015 From: qdunkan at gmail.com (Evan Laforge) Date: Tue, 16 Jun 2015 23:19:49 -0700 Subject: ghc 7.10.1 hard lock on exit with shake, OS X 10.10 In-Reply-To: References: Message-ID: I've been trying the 7.10.2 testing release for the last few days, and so far no lock-ups. Maybe that was it! On Tue, Jun 2, 2015 at 11:29 PM, Austin Seipp wrote: > Perhaps #10317 is related? > > https://ghc.haskell.org/trac/ghc/ticket/10317 > > You might try building with the latest ghc-7.10 branch. > > On Wed, Jun 3, 2015 at 12:27 AM, Evan Laforge wrote: >> On Tue, Jun 2, 2015 at 7:20 PM, Carter Schonwald >> wrote: >>> could you share a minimal program that reproduces the problem? >> >> That's the thing, it's a thousand line shakefile that builds a 100k >> line program, and it's happening only rarely now. Since it happens so >> rarely it seems really difficult to prune away bits to see if it still >> happens. I suppose since the building is all just running commands, >> the source it's building doesn't matter, but since it's a build, it >> runs a different sequence of commands every time. I suppose I could >> "stub out" the program by replacing ghc with a shell script that >> sleeps and touches the output files, but it feels like I could spend >> days on it because there are tons of little details. >> >> I'm pretty sure it's related to the threaded runtime, because it >> doesn't happen without -threaded. I could try with -debug, but that >> probably turns off -threaded too, so no more problem. Shake is >> heavily threaded and nondeterministic. I haven't seen other shake >> users report it though. >> _______________________________________________ >> Glasgow-haskell-users mailing list >> Glasgow-haskell-users at haskell.org >> http://mail.haskell.org/cgi-bin/mailman/listinfo/glasgow-haskell-users >> > > > > -- > Regards, > > Austin Seipp, Haskell Consultant > Well-Typed LLP, http://www.well-typed.com/ From hvr at gnu.org Thu Jun 18 08:32:05 2015 From: hvr at gnu.org (Herbert Valerio Riedel) Date: Thu, 18 Jun 2015 10:32:05 +0200 Subject: Native -XCPP Conclusion (was: RFC: "Native -XCPP" Proposal) In-Reply-To: <87zj5i55gs.fsf@gmail.com> (Herbert Valerio Riedel's message of "Wed, 06 May 2015 13:08:03 +0200") References: <87zj5i55gs.fsf@gmail.com> Message-ID: <87oakdo1ru.fsf@gmail.com> Hello *, Following up on the "Native -XCPP" Proposal discussion, it appears that cpphs' current LGPL+SLE licensing doesn't pose an *objective* showstopper problem but is rather more of an inconvenience as it causes argumentation/discussion overhead (which then /may/ actually result in Haskell being turned down eventually over alternatives that do without LGPL components). In order to acknowledge this discomfort, for GHC 7.12 we propose to follow "plan 4" according to [1] (i.e. calling out to a cpphs-executable as a separate process), thereby avoiding pulling any LGPL-subjected cpphs code into produced executables when linking against the 'ghc' package. "Plan 2" (i.e. embedding/linking cpphs' code directly into ghc) would reduce fork/exec overhead, which can be substantial on Windows [2], but plan 4 is no worse than what we have now. Last Call: Are there any objections with GHC adopting "plan 4"[1]? [1]: [2]: Thanks, HVR On 2015-05-06 at 13:08:03 +0200, Herbert Valerio Riedel wrote: > Hello *, > > As you may be aware, GHC's `{-# LANGUAGE CPP #-}` language extension > currently relies on the system's C-compiler bundled `cpp` program to > provide a "traditional mode" c-preprocessor. > > This has caused several problems in the past, since parsing Haskell code > with a preprocessor mode designed for use with C's tokenizer has caused > already quite some problems[1] in the past. I'd like to see GHC 7.12 > adopt an implemntation of `-XCPP` that does not rely on the shaky > system-`cpp` foundation. To this end I've created a wiki page > > https://ghc.haskell.org/trac/ghc/wiki/Proposal/NativeCpp > > to describe the actual problems in more detail, and a couple of possible > ways forward. Ideally, we'd simply integrate `cpphs` into GHC > (i.e. "plan 2"). However, due to `cpp`s non-BSD3 license this should be > discussed and debated since affects the overall-license of the GHC > code-base, which may or may not be a problem to GHC's user-base (and > that's what I hope this discussion will help to find out). > > So please go ahead and read the Wiki page... and then speak your mind! > > > Thanks, > HVR > > > [1]: ...does anybody remember the issues Haskell packages (& GHC) > encountered when Apple switched to the Clang tool-chain, thereby > causing code using `-XCPP` to suddenly break due to subtly > different `cpp`-semantics? -- "Elegance is not optional" -- Richard O'Keefe From marlowsd at gmail.com Fri Jun 19 18:48:48 2015 From: marlowsd at gmail.com (Simon Marlow) Date: Fri, 19 Jun 2015 19:48:48 +0100 Subject: Native -XCPP Conclusion In-Reply-To: <87oakdo1ru.fsf@gmail.com> References: <87zj5i55gs.fsf@gmail.com> <87oakdo1ru.fsf@gmail.com> Message-ID: <55846410.2060209@gmail.com> I have no problem with plan 4. However, I'll point out that implementing CPP is not *that* hard... :) Cheers, Simon On 18/06/2015 09:32, Herbert Valerio Riedel wrote: > Hello *, > > Following up on the "Native -XCPP" Proposal discussion, it appears that > cpphs' current LGPL+SLE licensing doesn't pose an *objective* > showstopper problem but is rather more of an inconvenience as it causes > argumentation/discussion overhead (which then /may/ actually result in > Haskell being turned down eventually over alternatives that do without > LGPL components). > > In order to acknowledge this discomfort, for GHC 7.12 we propose to follow > "plan 4" according to [1] (i.e. calling out to a cpphs-executable as a > separate process), thereby avoiding pulling any LGPL-subjected cpphs > code into produced executables when linking against the 'ghc' package. > > "Plan 2" (i.e. embedding/linking cpphs' code directly into ghc) would > reduce fork/exec overhead, which can be substantial on Windows [2], > but plan 4 is no worse than what we have now. > > Last Call: Are there any objections with GHC adopting "plan 4"[1]? > > [1]: > > [2]: > > Thanks, > HVR > > On 2015-05-06 at 13:08:03 +0200, Herbert Valerio Riedel wrote: >> Hello *, >> >> As you may be aware, GHC's `{-# LANGUAGE CPP #-}` language extension >> currently relies on the system's C-compiler bundled `cpp` program to >> provide a "traditional mode" c-preprocessor. >> >> This has caused several problems in the past, since parsing Haskell code >> with a preprocessor mode designed for use with C's tokenizer has caused >> already quite some problems[1] in the past. I'd like to see GHC 7.12 >> adopt an implemntation of `-XCPP` that does not rely on the shaky >> system-`cpp` foundation. To this end I've created a wiki page >> >> https://ghc.haskell.org/trac/ghc/wiki/Proposal/NativeCpp >> >> to describe the actual problems in more detail, and a couple of possible >> ways forward. Ideally, we'd simply integrate `cpphs` into GHC >> (i.e. "plan 2"). However, due to `cpp`s non-BSD3 license this should be >> discussed and debated since affects the overall-license of the GHC >> code-base, which may or may not be a problem to GHC's user-base (and >> that's what I hope this discussion will help to find out). >> >> So please go ahead and read the Wiki page... and then speak your mind! >> >> >> Thanks, >> HVR >> >> >> [1]: ...does anybody remember the issues Haskell packages (& GHC) >> encountered when Apple switched to the Clang tool-chain, thereby >> causing code using `-XCPP` to suddenly break due to subtly >> different `cpp`-semantics? > From marlowsd at gmail.com Fri Jun 19 19:51:56 2015 From: marlowsd at gmail.com (Simon Marlow) Date: Fri, 19 Jun 2015 20:51:56 +0100 Subject: -prof, -threaded, and -N In-Reply-To: <0334884B-2729-4E39-AEC2-2957D9B04C1A@kuhtz.eu> References: <0334884B-2729-4E39-AEC2-2957D9B04C1A@kuhtz.eu> Message-ID: <558472DC.6060502@gmail.com> That's a leftover from when profiling didn't support -N, I'll fix it. Thanks! Simon On 03/06/2015 07:03, Lars Kuhtz wrote: > From https://github.com/ghc/ghc/blob/master/rts/RtsFlags.c#L1238 it seems that the behavior described in my email below is intended: > > ``` > > if (rts_argv[arg][2] == '\0') { > #if defined(PROFILING) > RtsFlags.ParFlags.nNodes = 1; > #else > RtsFlags.ParFlags.nNodes = getNumberOfProcessors(); > #endif > ``` > > So, my question is: what is the reason for this difference between the profiling and the non-profiling case? > > Lars > >> On Jun 2, 2015, at 10:20 PM, Lars Kuhtz wrote: >> >> Hi, >> >> The behavior of the -N flag (without argument) with the profiling runtime seems inconsistent compared to the behavior without profiling. The following program >> >> ``` >> module Main where >> >> import GHC.Conc >> >> main :: IO () >> main = print numCapabilities >> ``` >> >> when compiled with `ghc -threaded -fforce-recomp Prof.hs` and run as `./Prof +RTS -N` prints `2` on my machine. When the same program is compiled with `ghc -threaded -fforce-recomp -prof Prof.hs` and executed as `./Prof +RTS -N` it prints `1`. >> >> When an argument is provided to `-N` (e.g. `./Prof +RTS -N2`) the profiling and non-profiling versions behave the same. >> >> I tested this with GHC-7.10.1 but I think that I already observed the same behavior with GHC-7.8. >> >> Is this inconsistency intended? >> >> Lars >> _______________________________________________ >> Glasgow-haskell-users mailing list >> Glasgow-haskell-users at haskell.org >> http://mail.haskell.org/cgi-bin/mailman/listinfo/glasgow-haskell-users >> > > _______________________________________________ > Glasgow-haskell-users mailing list > Glasgow-haskell-users at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/glasgow-haskell-users > From jerome.mahuet at gmail.com Mon Jun 22 10:56:41 2015 From: jerome.mahuet at gmail.com (=?UTF-8?Q?J=C3=A9rome_Mahuet?=) Date: Mon, 22 Jun 2015 12:56:41 +0200 Subject: Trouble building applications with Haskell GLUT and freeglut on OS X with GHC 7.10.1 In-Reply-To: References: Message-ID: Hello, When I depend on the GLUT Haskell package (2.6 or newer) on GHC 7.10.1 on OS X 10.10.3, the GLUT package builds and installs successfully, but applications that depend on GLUT fail during cabal install with this kind of linking error: can't load .so/.DLL for: /Users/jd/sandbox/.cabal-sandbox/lib/x86_64-osx-ghc-7.10.1/GLUT_J2ZZFJOYOcH4hQYFlXhEPp/libHSGLUT-2.7.0.1-0waW9bZutCf5s5H5zSV4Oh-ghc7.10.1.dylib (dlopen(/Users/jd/sandbox/.cabal-sandbox/lib/x86_64-osx-ghc-7.10.1/GLUT_J2ZZFJOYOcH4hQYFlXhEPp/libHSGLUT-2.7.0.1-0waW9bZutCf5s5H5zSV4Oh-ghc7.10.1.dylib, 5): Symbol not found: _glutBitmap8By13 Referenced from: /Users/jdsandbox/.cabal-sandbox/lib/x86_64-osx-ghc-7.10.1/GLUT_J2ZZFJOYOcH4hQYFlXhEPp/libHSGLUT-2.7.0.1-0waW9bZutCf5s5H5zSV4Oh-ghc7.10.1.dylib Expected in: flat namespace in /Users/jd/sandbox/.cabal-sandbox/lib/x86_64-osx-ghc-7.10.1/GLUT_J2ZZFJOYOcH4hQYFlXhEPp/libHSGLUT-2.7.0.1-0waW9bZutCf5s5H5zSV4Oh-ghc7.10.1.dylib) Occurs when trying to load GLUT to GHCi. $ ghci -package GLUT I tried loading the OSX's GLUT.framework manually: $ ghci -framework GLUT -package GLUT but it produces the same error message. To be sure I checked the OSX's GLUT.framework, it does contain the _glutBitmap8By13 symbol. It's also worth noticing that this only occurs on OS X with GHC 7.10.1 and cabal 1.22.*. linux + ghc 7.10.1 = Ok mac + ghc 7.10.1 = Fail mac + ghc 7.8.4 = Ok I'm not sure if this is a GHC or Cabal bug, but something is working differently on Mac with GHC 7.10.1/cabal 1.22.* Did you guys encounter something similar, is there a work-around we can do inside the GLUT Haskell package? From svenpanne at gmail.com Mon Jun 22 11:49:14 2015 From: svenpanne at gmail.com (Sven Panne) Date: Mon, 22 Jun 2015 13:49:14 +0200 Subject: Trouble building applications with Haskell GLUT and freeglut on OS X with GHC 7.10.1 In-Reply-To: References: Message-ID: Just a quick addition: The bug tracking this on the GLUT package side is https://github.com/haskell-opengl/GLUT/issues/19, and it seems to be a regression in the 7.10 series... -------------- next part -------------- An HTML attachment was scrubbed... URL: From qdunkan at gmail.com Tue Jun 23 17:08:44 2015 From: qdunkan at gmail.com (Evan Laforge) Date: Tue, 23 Jun 2015 10:08:44 -0700 Subject: ghc 7.10.1 hard lock on exit with shake, OS X 10.10 In-Reply-To: References: Message-ID: Oops, no it wasn't. Still getting lock-ups with 7.10.1.20150612, though they are rare. But this report seems not so useful since I don't really know how to make progress on reducing and reproducing. Maybe it's best to wait to see if any other reports come in. A large company doing many builds a day would see this a lot, so unless it's somehow specific to my configuration, eventually more reports should come in. On Tue, Jun 16, 2015 at 11:19 PM, Evan Laforge wrote: > I've been trying the 7.10.2 testing release for the last few days, and > so far no lock-ups. > Maybe that was it! > > On Tue, Jun 2, 2015 at 11:29 PM, Austin Seipp wrote: >> Perhaps #10317 is related? >> >> https://ghc.haskell.org/trac/ghc/ticket/10317 >> >> You might try building with the latest ghc-7.10 branch. >> >> On Wed, Jun 3, 2015 at 12:27 AM, Evan Laforge wrote: >>> On Tue, Jun 2, 2015 at 7:20 PM, Carter Schonwald >>> wrote: >>>> could you share a minimal program that reproduces the problem? >>> >>> That's the thing, it's a thousand line shakefile that builds a 100k >>> line program, and it's happening only rarely now. Since it happens so >>> rarely it seems really difficult to prune away bits to see if it still >>> happens. I suppose since the building is all just running commands, >>> the source it's building doesn't matter, but since it's a build, it >>> runs a different sequence of commands every time. I suppose I could >>> "stub out" the program by replacing ghc with a shell script that >>> sleeps and touches the output files, but it feels like I could spend >>> days on it because there are tons of little details. >>> >>> I'm pretty sure it's related to the threaded runtime, because it >>> doesn't happen without -threaded. I could try with -debug, but that >>> probably turns off -threaded too, so no more problem. Shake is >>> heavily threaded and nondeterministic. I haven't seen other shake >>> users report it though. >>> _______________________________________________ >>> Glasgow-haskell-users mailing list >>> Glasgow-haskell-users at haskell.org >>> http://mail.haskell.org/cgi-bin/mailman/listinfo/glasgow-haskell-users >>> >> >> >> >> -- >> Regards, >> >> Austin Seipp, Haskell Consultant >> Well-Typed LLP, http://www.well-typed.com/ From gershomb at gmail.com Fri Jun 26 14:53:40 2015 From: gershomb at gmail.com (Gershom B) Date: Fri, 26 Jun 2015 10:53:40 -0400 Subject: tweaking text on the ghc downloads page Message-ID: I know there is a plan for some broader ghc webpage redesign. In the meantime, apparently people find the current "Stop" text terribly troublesome. This is because, of course, it points to the platform and now some people believe that a minimal distribution is more usable, etc. Just to take this issue off the agenda, I would like, if there are no objections, to just change that text as follows. Current: "Stop! For most users, we recommend installing the _Haskell Platform_ instead of GHC. The current Haskell Platform release includes a recent GHC release as well as some other tools (such as cabal), and a larger set of libraries that are known to work together." Proposed: "Stop! For most users, we recommend installing _a proper distribution_ instead of just GHC. A distribution includes a recent GHC release as well as other important tools (such as cabal, for installing libraries), and potentially a broader set of libraries known to work together." And where before the "Haskell Platform" text would link to of course the platform page, the new "proper distribution" text would now link to https://www.haskell.org/downloads where we could then argue to our heart's content about the best way to present the various download and installation options as we go forward. So, this doesn't resolve any controversy, but it at least centralizes it. If there's no objection, I'll try to get to this tomorrow? --Gershom -------------- next part -------------- An HTML attachment was scrubbed... URL: From michael at snoyman.com Fri Jun 26 14:58:56 2015 From: michael at snoyman.com (Michael Snoyman) Date: Fri, 26 Jun 2015 14:58:56 +0000 Subject: tweaking text on the ghc downloads page In-Reply-To: References: Message-ID: One point I've seen users confused about in the past is that some guides recommend downloading GHC directly as part of setting up a full distribution, e.g.: https://www.haskell.org/downloads/linux (manual install) I'd take the STOP out entirely, and just give a link to the /downloads page, to avoid this confusion. The rest of your text looks spot on to me, it's literally the one word "STOP" that seems to have people out of sorts most often. On Fri, Jun 26, 2015 at 5:54 PM Gershom B wrote: > I know there is a plan for some broader ghc webpage redesign. > > In the meantime, apparently people find the current "Stop" text terribly > troublesome. This is because, of course, it points to the platform and now > some people believe that a minimal distribution is more usable, etc. > > Just to take this issue off the agenda, I would like, if there are no > objections, to just change that text as follows. > > Current: > > "Stop! > > For most users, we recommend installing the _Haskell Platform_ instead of > GHC. The current Haskell Platform release includes a recent GHC release as > well as some other tools (such as cabal), and a larger set of libraries > that are known to work together." > > Proposed: > > "Stop! > > For most users, we recommend installing _a proper distribution_ instead of > just GHC. A distribution includes a recent GHC release as well as other > important tools (such as cabal, for installing libraries), and potentially > a broader set of libraries known to work together." > > And where before the "Haskell Platform" text would link to of course the > platform page, the new "proper distribution" text would now link to > https://www.haskell.org/downloads where we could then argue to our > heart's content about the best way to present the various download and > installation options as we go forward. > > So, this doesn't resolve any controversy, but it at least centralizes it. > > If there's no objection, I'll try to get to this tomorrow? > > --Gershom > _______________________________________________ > Glasgow-haskell-users mailing list > Glasgow-haskell-users at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/glasgow-haskell-users > -------------- next part -------------- An HTML attachment was scrubbed... URL: From simonpj at microsoft.com Fri Jun 26 15:03:01 2015 From: simonpj at microsoft.com (Simon Peyton Jones) Date: Fri, 26 Jun 2015 15:03:01 +0000 Subject: tweaking text on the ghc downloads page In-Reply-To: References: Message-ID: <5412f858fe77423380c18d2ca5a6e4a2@DB4PR30MB030.064d.mgd.msft.net> I?m ok with all of this, but I?d like just to check with Mark L to see how he suggests signposting the HP Simon From: Glasgow-haskell-users [mailto:glasgow-haskell-users-bounces at haskell.org] On Behalf Of Michael Snoyman Sent: 26 June 2015 15:59 To: Gershom B; Glasgow-Haskell-Users users Subject: Re: tweaking text on the ghc downloads page One point I've seen users confused about in the past is that some guides recommend downloading GHC directly as part of setting up a full distribution, e.g.: https://www.haskell.org/downloads/linux (manual install) I'd take the STOP out entirely, and just give a link to the /downloads page, to avoid this confusion. The rest of your text looks spot on to me, it's literally the one word "STOP" that seems to have people out of sorts most often. On Fri, Jun 26, 2015 at 5:54 PM Gershom B > wrote: I know there is a plan for some broader ghc webpage redesign. In the meantime, apparently people find the current "Stop" text terribly troublesome. This is because, of course, it points to the platform and now some people believe that a minimal distribution is more usable, etc. Just to take this issue off the agenda, I would like, if there are no objections, to just change that text as follows. Current: "Stop! For most users, we recommend installing the _Haskell Platform_ instead of GHC. The current Haskell Platform release includes a recent GHC release as well as some other tools (such as cabal), and a larger set of libraries that are known to work together." Proposed: "Stop! For most users, we recommend installing _a proper distribution_ instead of just GHC. A distribution includes a recent GHC release as well as other important tools (such as cabal, for installing libraries), and potentially a broader set of libraries known to work together." And where before the "Haskell Platform" text would link to of course the platform page, the new "proper distribution" text would now link to https://www.haskell.org/downloads where we could then argue to our heart's content about the best way to present the various download and installation options as we go forward. So, this doesn't resolve any controversy, but it at least centralizes it. If there's no objection, I'll try to get to this tomorrow? --Gershom _______________________________________________ Glasgow-haskell-users mailing list Glasgow-haskell-users at haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/glasgow-haskell-users -------------- next part -------------- An HTML attachment was scrubbed... URL: From gershomb at gmail.com Fri Jun 26 15:05:33 2015 From: gershomb at gmail.com (Gershom B) Date: Fri, 26 Jun 2015 11:05:33 -0400 Subject: tweaking text on the ghc downloads page In-Reply-To: <5412f858fe77423380c18d2ca5a6e4a2@DB4PR30MB030.064d.mgd.msft.net> References: <5412f858fe77423380c18d2ca5a6e4a2@DB4PR30MB030.064d.mgd.msft.net> Message-ID: Sure. Ccing him on this thread now. (Note that we?re having a seperate discussion he?s involved with on -infra about signposting the HP and other options on the haskell.org/downloads?page ? so this is in a sense, about just making sure we only have the one big bikeshed to color rather than many little ones :-P) ?Gershom On June 26, 2015 at 11:03:33 AM, Simon Peyton Jones (simonpj at microsoft.com) wrote: > I?m ok with all of this, but I?d like just to check with Mark L to see how he suggests signposting > the HP > > Simon > > From: Glasgow-haskell-users [mailto:glasgow-haskell-users-bounces at haskell.org] > On Behalf Of Michael Snoyman > Sent: 26 June 2015 15:59 > To: Gershom B; Glasgow-Haskell-Users users > Subject: Re: tweaking text on the ghc downloads page > > One point I've seen users confused about in the past is that some guides recommend downloading > GHC directly as part of setting up a full distribution, e.g.: > > https://www.haskell.org/downloads/linux (manual install) > I'd take the STOP out entirely, and just give a link to the /downloads page, to avoid this > confusion. The rest of your text looks spot on to me, it's literally the one word "STOP" > that seems to have people out of sorts most often. > > On Fri, Jun 26, 2015 at 5:54 PM Gershom B > > wrote: > I know there is a plan for some broader ghc webpage redesign. > > In the meantime, apparently people find the current "Stop" text terribly troublesome. > This is because, of course, it points to the platform and now some people believe that > a minimal distribution is more usable, etc. > > Just to take this issue off the agenda, I would like, if there are no objections, to just > change that text as follows. > > Current: > > "Stop! > > For most users, we recommend installing the _Haskell Platform_ instead of GHC. The current > Haskell Platform release includes a recent GHC release as well as some other tools (such > as cabal), and a larger set of libraries that are known to work together." > > Proposed: > > "Stop! > > For most users, we recommend installing _a proper distribution_ instead of just GHC. > A distribution includes a recent GHC release as well as other important tools (such as > cabal, for installing libraries), and potentially a broader set of libraries known > to work together." > > And where before the "Haskell Platform" text would link to of course the platform page, > the new "proper distribution" text would now link to https://www.haskell.org/downloads > where we could then argue to our heart's content about the best way to present the various > download and installation options as we go forward. > > So, this doesn't resolve any controversy, but it at least centralizes it. > > If there's no objection, I'll try to get to this tomorrow? > > --Gershom > _______________________________________________ > Glasgow-haskell-users mailing list > Glasgow-haskell-users at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/glasgow-haskell-users > From gershomb at gmail.com Sun Jun 28 08:47:17 2015 From: gershomb at gmail.com (Gershom B) Date: Sun, 28 Jun 2015 04:47:17 -0400 Subject: tweaking text on the ghc downloads page In-Reply-To: References: <5412f858fe77423380c18d2ca5a6e4a2@DB4PR30MB030.064d.mgd.msft.net> Message-ID: Ok, this is now done. Rather than ?Stop? it now says the hopefully slightly less confusing ?Take Notice,? and the text is otherwise as I proposed. I agree that this is only a tiny step in a more general streamining of this whole process. Cheers, Gershom On June 26, 2015 at 11:29:25 AM, Mark Lentczner (mark.lentczner at gmail.com) wrote: > Well - it isn't objectionable.... but it is, at best, a stop gap. > > Ultimately, what people want when they want to get Haskell installed is a > big button marked "Download" - that when pressed starts the download > immediately. This is true for beginners and seasoned users alike. It is > true on all web sites for all things. > > Every link we put in their way looses some percentage, and increases the > frustration of others. This change makes it: > > > 1) Google search GHC > > 2) "Latest news...", search and find Download in left bar, click > > 3) "Stop! ...", click downloads > 4) "You've got options ...", click "Platform > 5) "Download button", click > > > (That last one is actually another click and page load, but we'll be > putting the download buttons on the first Platform page in this round.) > > The Platform team built and proposed a page for #3 (the > haskell.org/downloads) page, that included the Download button for Platform > on the detected users's OS, and had top bar links to other options. The > sequence should be this: > > 1) Google search GHC > > 2) "GHC is cool... Get it with a full Haskell distribution", click > > 3) (on haskell.org/downloads): "Download Haskell Platform... Download > button", click > > A page for #3 was built by the Haskell Platform team that included links to > other options. You can preview it here: > > http://45.55.156.136:8000/demo-3200/download-plan-a2.html > > > ? Mark >