From ghc-devs at haskell.org Thu Jun 1 04:57:30 2017 From: ghc-devs at haskell.org (GHC) Date: Thu, 01 Jun 2017 04:57:30 -0000 Subject: [GHC] #13774: Singletons code fails to typecheck when type signature involving type family is added Message-ID: <050.ab332347289424d0148182ea2be617f8@haskell.org> #13774: Singletons code fails to typecheck when type signature involving type family is added -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 (Type checker) | Keywords: TypeFamilies | Operating System: Unknown/Multiple Architecture: | Type of failure: GHC rejects Unknown/Multiple | valid program Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- Yes, I know "singletons" is in the title... but the code isn't //that// scary, I promise. Here's some code which //does// typecheck: {{{#!hs {-# LANGUAGE FunctionalDependencies #-} {-# LANGUAGE GADTs #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE TypeInType #-} module Bug where data family Sing (a :: k) data Nat = Zero | Succ Nat data instance Sing (b :: Bool) where SFalse :: Sing 'False STrue :: Sing 'True data instance Sing (n :: Nat) where SZero :: Sing 'Zero SSucc :: Sing n -> Sing ('Succ n) type family Not (x :: Bool) :: Bool where Not 'True = 'False Not 'False = 'True sNot :: Sing b -> Sing (Not b) sNot STrue = SFalse sNot SFalse = STrue class PFD a b | a -> b where type L2r (x :: a) :: b instance PFD Bool Nat where type L2r 'False = 'Zero type L2r 'True = 'Succ 'Zero type T2 = L2r 'False class SFD a b | a -> b where sL2r :: forall (x :: a). Sing x -> Sing (L2r x :: b) instance SFD Bool Nat where sL2r SFalse = SZero sL2r STrue = SSucc SZero sT2 = sL2r SFalse }}} It also typechecks if you give `sT2` this particular type signature: {{{#!hs sT2 :: Sing 'Zero sT2 = sL2r SFalse }}} However, if you give it either of these two type signatures: {{{#!hs sT2 :: Sing T2 }}} {{{#!hs sT2 :: Sing (L2r 'False) }}} Then GHC 8.0.1, 8.0.2, 8.2.1, and HEAD will choke: {{{ GHCi, version 8.2.0.20170522: http://www.haskell.org/ghc/ :? for help Loaded GHCi configuration from /home/rgscott/.ghci [1 of 1] Compiling Bug ( Bug.hs, interpreted ) Bug.hs:46:7: error: • No instance for (SFD Bool k) arising from a use of ‘sL2r’ • In the expression: sL2r SFalse In an equation for ‘sT2’: sT2 = sL2r SFalse | 46 | sT2 = sL2r SFalse | ^^^^^^^^^^^ }}} At this point, I get the urge to yell obscenities at GHC, because there definitely //is// an instance of the form `SFD Bool k` in scope (and moreover, `SFD`'s functional dependency should make sure that `k ~ Nat`). Shouldn't it be using that? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jun 1 06:51:20 2017 From: ghc-devs at haskell.org (GHC) Date: Thu, 01 Jun 2017 06:51:20 -0000 Subject: [GHC] #13185: haskell-relational-query: ghc: panic! (the 'impossible' happened) In-Reply-To: <052.7cf8871089bbe0aab7ba792447e09946@haskell.org> References: <052.7cf8871089bbe0aab7ba792447e09946@haskell.org> Message-ID: <067.6e3849105c2018b38e88134268ecdba7@haskell.org> #13185: haskell-relational-query: ghc: panic! (the 'impossible' happened) -------------------------------------+------------------------------------- Reporter: LocutusOfBorg | Owner: (none) Type: bug | Status: new Priority: high | Milestone: Component: Compiler | Version: 8.0.2 Resolution: | Keywords: Operating System: Linux | Architecture: | Unknown/Multiple Type of failure: Compile-time | Test Case: build crash or panic | relational-query with ghc 8.0.2 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): The bug exists somewhere between 7c216d2ab84bd5f8140952cba0a48cedfab13f7e and ae94a31e7f162b4a3ef6b6f837bd6006a98f639a. Unfortunately, none of the commits between them compile, so I can't narrow it down further than that. All of the commits in that range, however, are authored by niteria and involve determinism in one way or another. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jun 1 08:48:37 2017 From: ghc-devs at haskell.org (GHC) Date: Thu, 01 Jun 2017 08:48:37 -0000 Subject: [GHC] #8272: testing if SpLim=$rbp and Sp=$rsp changed performance at all In-Reply-To: <045.ecd7af4f53d7df1147bf6a068ec1e485@haskell.org> References: <045.ecd7af4f53d7df1147bf6a068ec1e485@haskell.org> Message-ID: <060.ca64de6659e3417fd38a9800af980ffa@haskell.org> #8272: testing if SpLim=$rbp and Sp=$rsp changed performance at all -------------------------------------+------------------------------------- Reporter: carter | Owner: carter Type: task | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.7 Resolution: | Keywords: | callingConvention Operating System: Unknown/Multiple | Architecture: x86_64 Type of failure: Runtime | (amd64) performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonmar): @bgamari: doesn't the DWARF stack unwinding support that you've been working on help with `perf`? @michalt: I think we have to do (1) in order to do call/ret, because otherwise the stack would be split over two places, and the RTS would have a terrible time walking it. Or perhaps I've misunderstood what you mean? I'm actually not all that enthusiastic about the proposal having just re- read https://github.com/ghc-proposals/ghc-proposals/pull/17. The benefits are small or are actually regressions (code size and the overhead for jmp after call) and it's a huge upheaval. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jun 1 09:39:07 2017 From: ghc-devs at haskell.org (GHC) Date: Thu, 01 Jun 2017 09:39:07 -0000 Subject: [GHC] #13772: Cannot put HasCallStack on instances In-Reply-To: <047.d360e3ed5517211c4a279da62bac67fe@haskell.org> References: <047.d360e3ed5517211c4a279da62bac67fe@haskell.org> Message-ID: <062.c80c44954a53c80c87bf673d89865619@haskell.org> #13772: Cannot put HasCallStack on instances -------------------------------------+------------------------------------- Reporter: augustss | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by Iceland_jack): * cc: Iceland_jack (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jun 1 10:35:38 2017 From: ghc-devs at haskell.org (GHC) Date: Thu, 01 Jun 2017 10:35:38 -0000 Subject: [GHC] #13775: Type family expansion is too lazy, allows accepting of ill-typed terms Message-ID: <045.09c124a40b32f046227808df7e0aa665@haskell.org> #13775: Type family expansion is too lazy, allows accepting of ill-typed terms -------------------------------------+------------------------------------- Reporter: fizruk | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.2 (Type checker) | Keywords: | Operating System: MacOS X Architecture: x86_64 | Type of failure: GHC accepts (amd64) | invalid program Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- I'm using GHC 8.0.2 and I've just witnessed a weird bug. To reproduce a bug I use this type family, using `TypeError` (this is a minimal type family I could get to keep bug reproducible): {{{ {-# LANGUAGE DataKinds #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE TypeOperators #-} {-# LANGUAGE UndecidableInstances #-} import GHC.TypeLits type family Head xs where Head '[] = TypeError (Text "empty list") Head (x ': xs) = x }}} Then I go to GHCi, load this code and observe this: {{{ >>> show (Proxy @ (Head '[])) "Proxy" }}} This looks like a bug to me! I expect `Head '[]` to produce a type error. And indeed it does, if I ask differently: {{{ >>> Proxy @ (Head '[]) :9:1: error: • empty list • When checking the inferred type it :: Proxy (TypeError ...) }}} So far it looks like `show` somehow "lazily" evaluates it's argument type and that's why it's possible to `show Proxy` even when `Proxy` is ill- typed. But if I expand `Head '[]` manually then it all works as expected again: {{{ >>> show $ Proxy @ (TypeError (Text "error")) :13:8: error: • error • In the second argument of ‘($)’, namely ‘Proxy @(TypeError (Text "error"))’ In the expression: show $ Proxy @(TypeError (Text "error")) In an equation for ‘it’: it = show $ Proxy @(TypeError (Text "error")) }}} You can remove `TypeError` from the original type family: {{{ type family Head xs where Head (x ': xs) = x }}} And it gets even weirder: {{{ >>> show (Proxy @ (Head '[])) "Proxy" >>> Proxy @ (Head '[]) Proxy }}} I did not test this with GHC 8.2. I think this behaviour is not critical for me, but accepting ill-typed terms looks like a bad sign, especially for type-level-heavy programs. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jun 1 12:36:10 2017 From: ghc-devs at haskell.org (GHC) Date: Thu, 01 Jun 2017 12:36:10 -0000 Subject: [GHC] #13767: GHCi trips -DS checks at rts/sm/Sanity.c, line 210 In-Reply-To: <046.e0bf705a7b0da22195c9831465099e74@haskell.org> References: <046.e0bf705a7b0da22195c9831465099e74@haskell.org> Message-ID: <061.82f510f2e80b141475217cc0fb25fa97@haskell.org> #13767: GHCi trips -DS checks at rts/sm/Sanity.c, line 210 -------------------------------------+------------------------------------- Reporter: niteria | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Runtime System | Version: 8.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by niteria): https://phabricator.haskell.org/rGHC4848ab9ce3c4491935888d405412d451294b74ee works 1k commits to bisect. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jun 1 12:56:32 2017 From: ghc-devs at haskell.org (GHC) Date: Thu, 01 Jun 2017 12:56:32 -0000 Subject: [GHC] #8272: testing if SpLim=$rbp and Sp=$rsp changed performance at all In-Reply-To: <045.ecd7af4f53d7df1147bf6a068ec1e485@haskell.org> References: <045.ecd7af4f53d7df1147bf6a068ec1e485@haskell.org> Message-ID: <060.be0061d4c5505a3598b2d0cb52ebd8b4@haskell.org> #8272: testing if SpLim=$rbp and Sp=$rsp changed performance at all -------------------------------------+------------------------------------- Reporter: carter | Owner: carter Type: task | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.7 Resolution: | Keywords: | callingConvention Operating System: Unknown/Multiple | Architecture: x86_64 Type of failure: Runtime | (amd64) performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by carter): @simonmar the stack pointer experiment sans call and rest might still be worth measuring,yes? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jun 1 13:04:29 2017 From: ghc-devs at haskell.org (GHC) Date: Thu, 01 Jun 2017 13:04:29 -0000 Subject: [GHC] #13771: ghc fails to build on openSUSE In-Reply-To: <048.545d3232bdf47d2b254b3d958c840fde@haskell.org> References: <048.545d3232bdf47d2b254b3d958c840fde@haskell.org> Message-ID: <063.43fa3de123893f9a4cefd70f12102c6a@haskell.org> #13771: ghc fails to build on openSUSE ---------------------------------+-------------------------------------- Reporter: msuchanek | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.2 Resolution: | Keywords: Operating System: Linux | Architecture: x86_64 (amd64) Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | ---------------------------------+-------------------------------------- Comment (by msuchanek): ok, so as I understand the issue distributions are moving towards compiling with -fPIE -pie or whatever is the current flag for whatever reason. It seems on SUSE these flags are added to rpm flags on the build service meaning system binaries are built with them but locally compiled binaries are not. Adding these flags requires that object files must be built with -fPIC and gcc complains if it is not the case and refuses to link binaries. == Issue: gcc started using PIE on system with ghc installed ==== simulation: {{{ # mv /usr/bin/gcc /usr/bin/gcc.real cat > /usr/bin/gcc < int main(int argc, char** argv) { puts("Hello World!"); } }}} {{{ $ gcc -fno-pic -c -Wall hello_world.c -o hello_world.o $ gcc hello_world.o -o hello_world /usr/lib64/gcc/x86_64-suse-linux/6/../../../../x86_64-suse-linux/bin/ld: hello_world.o: relocation R_X86_64_32 against `.rodata' can not be used when making a shared object; recompile with -fPIC hello_world.o: error adding symbols: Bad value collect2: error: ld returned 1 exit status $ gcc -no-pie hello_world.o -o hello_world $ ./hello_world Hello World! }}} So gcc defaulting to PIE should be detected at bootstrap and at binary distribution installation and -fPIC should be added as default ghc flag. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jun 1 13:26:03 2017 From: ghc-devs at haskell.org (GHC) Date: Thu, 01 Jun 2017 13:26:03 -0000 Subject: [GHC] #13775: Type family expansion is too lazy, allows accepting of ill-typed terms In-Reply-To: <045.09c124a40b32f046227808df7e0aa665@haskell.org> References: <045.09c124a40b32f046227808df7e0aa665@haskell.org> Message-ID: <060.1cd2fb42d948a89f11adc73e65a6a754@haskell.org> #13775: Type family expansion is too lazy, allows accepting of ill-typed terms -------------------------------------+------------------------------------- Reporter: fizruk | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.2 checker) | Keywords: Resolution: | CustomTypeErrors Operating System: Unknown/Multiple | Architecture: Type of failure: GHC accepts | Unknown/Multiple invalid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * keywords: => CustomTypeErrors * os: MacOS X => Unknown/Multiple * architecture: x86_64 (amd64) => Unknown/Multiple Comment: Also reproducible in GHC 8.2 and HEAD. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jun 1 13:29:30 2017 From: ghc-devs at haskell.org (GHC) Date: Thu, 01 Jun 2017 13:29:30 -0000 Subject: [GHC] #12237: Constraint resolution vs. type family resolution vs. TypeErrors In-Reply-To: <045.5325fbebd78f42603d0934e538267733@haskell.org> References: <045.5325fbebd78f42603d0934e538267733@haskell.org> Message-ID: <060.44172a51454f74cd696f53556e945264@haskell.org> #12237: Constraint resolution vs. type family resolution vs. TypeErrors -------------------------------------+------------------------------------- Reporter: cactus | Owner: (none) Type: feature request | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: duplicate | Keywords: | CustomTypeErrors Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Other | Test Case: Blocked By: | Blocking: Related Tickets: #11990 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * status: new => closed * resolution: => duplicate Comment: Indeed, this is fixed in 8.0.2. This test case is sufficiently similar to the one in #11990 that I'll close this as a duplicate. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jun 1 13:40:22 2017 From: ghc-devs at haskell.org (GHC) Date: Thu, 01 Jun 2017 13:40:22 -0000 Subject: [GHC] #13775: Type family expansion is too lazy, allows accepting of ill-typed terms In-Reply-To: <045.09c124a40b32f046227808df7e0aa665@haskell.org> References: <045.09c124a40b32f046227808df7e0aa665@haskell.org> Message-ID: <060.1314e35220eaa4e4fac5d448b435feb5@haskell.org> #13775: Type family expansion is too lazy, allows accepting of ill-typed terms -------------------------------------+------------------------------------- Reporter: fizruk | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.2 checker) | Keywords: Resolution: | CustomTypeErrors Operating System: Unknown/Multiple | Architecture: Type of failure: GHC accepts | Unknown/Multiple invalid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by fizruk): By the way, if you mistype `Proxy` as `Prox`, you can also get GHC panic: {{{ >>> Prox @ (Head '[]) ghc: panic! (the 'impossible' happened) (GHC version 8.0.2 for x86_64-apple-darwin): initTc: unsolved constraints WC {wc_insol = [W] Prox_a1L4 :: t_a1L3[tau:1] (CHoleCan: Prox) [W] Prox_a1Ls :: t_a1Lr[tau:1] (CHoleCan: Prox)} Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug }}} But this panic seems to be because of `TypeApplications` and can be reproduced with just two lines in GHCi: {{{ >>> :set -XTypeApplications >>> X @ Int ghc: panic! (the 'impossible' happened) (GHC version 8.0.2 for x86_64-apple-darwin): initTc: unsolved constraints WC {wc_insol = [W] X_a13x :: t_a13w[tau:1] (CHoleCan: X) [W] X_a13V :: t_a13U[tau:1] (CHoleCan: X)} Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug }}} Should I file this one separately? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jun 1 13:43:08 2017 From: ghc-devs at haskell.org (GHC) Date: Thu, 01 Jun 2017 13:43:08 -0000 Subject: [GHC] #13775: Type family expansion is too lazy, allows accepting of ill-typed terms In-Reply-To: <045.09c124a40b32f046227808df7e0aa665@haskell.org> References: <045.09c124a40b32f046227808df7e0aa665@haskell.org> Message-ID: <060.6f15994ff446c1049855b251c8766263@haskell.org> #13775: Type family expansion is too lazy, allows accepting of ill-typed terms -------------------------------------+------------------------------------- Reporter: fizruk | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.2 checker) | Keywords: Resolution: | CustomTypeErrors Operating System: Unknown/Multiple | Architecture: Type of failure: GHC accepts | Unknown/Multiple invalid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): That one is actually a known bug (#13466) which has been fixed in GHC 8.2.1. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jun 1 13:48:06 2017 From: ghc-devs at haskell.org (GHC) Date: Thu, 01 Jun 2017 13:48:06 -0000 Subject: [GHC] #13774: Singletons code fails to typecheck when type signature involving type family is added In-Reply-To: <050.ab332347289424d0148182ea2be617f8@haskell.org> References: <050.ab332347289424d0148182ea2be617f8@haskell.org> Message-ID: <065.936f5d1705bd673ea38e15e04c7ba3e2@haskell.org> #13774: Singletons code fails to typecheck when type signature involving type family is added -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.1 checker) | Keywords: FunDeps, Resolution: | TypeFamilies Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * cc: goldfire (added) * keywords: TypeFamilies => FunDeps, TypeFamilies Comment: Some possible wisdom from the `singletons` [https://github.com/goldfirere/singletons/tree/f9910fef9084ad9e3ca6b4f713c882aff2eea7ac #known-bugs README]: > Inference dependent on functional dependencies is unpredictably bad. The problem is that a use of an associated type family tied to a class with fundeps doesn't provoke the fundep to kick in. This is GHC's problem, in the end. And this [https://github.com/goldfirere/singletons/issues/37#issuecomment-41488816 comment]: > If only a type family could have functional dependencies, we could get somewhere, but alas, no. (Sidenote: of course, a type family can be declared within a class with functional dependencies, but GHC doesn't apply the fundeps when examining the type family.) I was unable to dig up anything which explained these comments. Richard, can you elaborate more on this interaction between type families and functional dependencies? Is there an existing ticket which describes the root issue? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jun 1 16:17:53 2017 From: ghc-devs at haskell.org (GHC) Date: Thu, 01 Jun 2017 16:17:53 -0000 Subject: [GHC] #8703: Use guard pages rather than heap checks In-Reply-To: <046.cc8df1f4c44d21b3204aafaf538413fa@haskell.org> References: <046.cc8df1f4c44d21b3204aafaf538413fa@haskell.org> Message-ID: <061.9fe2e2597afd451604a65c046321c9ac@haskell.org> #8703: Use guard pages rather than heap checks -------------------------------------+------------------------------------- Reporter: schyler | Owner: simonmar Type: feature request | Status: closed Priority: normal | Milestone: Component: Runtime System | Version: Resolution: wontfix | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by varosi): Fantastic paper! Thanks for the thorough answers! Did that plan from the paper happened already in the latest GHC: 7.2 Privatising minor collections This looks like a very good fit for per-core caches. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jun 1 17:31:12 2017 From: ghc-devs at haskell.org (GHC) Date: Thu, 01 Jun 2017 17:31:12 -0000 Subject: [GHC] #13774: Singletons code fails to typecheck when type signature involving type family is added In-Reply-To: <050.ab332347289424d0148182ea2be617f8@haskell.org> References: <050.ab332347289424d0148182ea2be617f8@haskell.org> Message-ID: <065.cf6671f680c34d1e7898f4cd80bd1fb5@haskell.org> #13774: Singletons code fails to typecheck when type signature involving type family is added -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.1 checker) | Keywords: FunDeps, Resolution: | TypeFamilies Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by goldfire): I don't think this is related to those comments. To explain those comments: {{{ class C a b | a -> b where f :: a -> b class PC a b | a -> b where type F (x :: a) :: b }}} A use of `f` will trigger a need for a `C` instance. But a use of `F` won't. So, an inference that succeeds on terms fails on types. But that's not what's going on here. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jun 1 17:52:02 2017 From: ghc-devs at haskell.org (GHC) Date: Thu, 01 Jun 2017 17:52:02 -0000 Subject: [GHC] #13757: Are you for or against writing "otherwise" as a keyword? In-Reply-To: <044.a4fc99e00f379531d171337bd3da9d21@haskell.org> References: <044.a4fc99e00f379531d171337bd3da9d21@haskell.org> Message-ID: <059.b52ec0a1e0d4c6dd73cd41819a4b5642@haskell.org> #13757: Are you for or against writing "otherwise" as a keyword? -------------------------------------+------------------------------------- Reporter: vanto | Owner: (none) Type: feature request | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 8.0.2 Resolution: invalid | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Poor/confusing | Unknown/Multiple error message | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by goldfire): * status: new => closed * resolution: => invalid Comment: While I appreciate your search for simplicity in posting proposals here to Trac, the community has decided that the place for proposals is https://github.com/ghc-proposals/ghc-proposals. Having two places for proposals is not a good idea, in my opinion. So, I continue to urge you to place your proposal on GitHub. If you run into trouble following the instructions there, feel free to ask questions. Looking over your proposal attachment, that will need to be much more detailed for a real proposal. For example, the motivation reads "I think this make good sense." But you have to explain why so that others might come to agree with you. Until you go through this community-decided proposal process, we can't make further progress here. Because this ticket is in the wrong place (Trac instead of GitHub), I am closing. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jun 1 18:38:38 2017 From: ghc-devs at haskell.org (GHC) Date: Thu, 01 Jun 2017 18:38:38 -0000 Subject: [GHC] #13757: Are you for or against writing "otherwise" as a keyword? In-Reply-To: <044.a4fc99e00f379531d171337bd3da9d21@haskell.org> References: <044.a4fc99e00f379531d171337bd3da9d21@haskell.org> Message-ID: <059.ab0e0da2365f2a3c3b4162d45e4cd1f2@haskell.org> #13757: Are you for or against writing "otherwise" as a keyword? -------------------------------------+------------------------------------- Reporter: vanto | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Poor/confusing | Unknown/Multiple error message | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by vanto): * status: closed => new * resolution: invalid => Comment: Thanks.\\ The community has decided that the place for proposals is ​https://github.com/ghc-proposals/ghc-proposals.\\ Ok!.\\ But the situation may have changed?\\ Nothing is frozen in this world.\\ You gave your opinion.\\ But you are not alone in the Committee.\\ Maybe someone would agree?\\ When I take a look at your cv in the Committee, in the line where it is written "Committer since: ..." it is noted "May, 2012".\\ Maybe the senior have their words to say?.\\ I reopen this ticket. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jun 1 20:28:40 2017 From: ghc-devs at haskell.org (GHC) Date: Thu, 01 Jun 2017 20:28:40 -0000 Subject: [GHC] #12545: Compilation time/space regression in GHC 8.0/8.1 (search in type-level lists and -O) In-Reply-To: <057.9aecaec89b7fd255565e55bac0801cc6@haskell.org> References: <057.9aecaec89b7fd255565e55bac0801cc6@haskell.org> Message-ID: <072.7c5ad36d8c8a44e174b65ea538576814@haskell.org> #12545: Compilation time/space regression in GHC 8.0/8.1 (search in type-level lists and -O) -------------------------------------+------------------------------------- Reporter: | Owner: (none) mikhail.vorozhtsov | Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Inlining Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by nh2): * cc: nh2 (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jun 1 20:43:55 2017 From: ghc-devs at haskell.org (GHC) Date: Thu, 01 Jun 2017 20:43:55 -0000 Subject: [GHC] #13776: -ddump-splices produces unnecessarily qualified names for tuple and list types Message-ID: <050.87f5b641e82d5f06fa4748e90b74c406@haskell.org> #13776: -ddump-splices produces unnecessarily qualified names for tuple and list types -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Template | Version: 8.0.1 Haskell | Keywords: newcomer | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- If you compile this: {{{#!hs {-# LANGUAGE TemplateHaskell #-} {-# OPTIONS_GHC -ddump-splices #-} module Bug where import Language.Haskell.TH f :: $(conT ''(,) `appT` conT ''Int `appT` conT ''Int) f = (1,2) g :: $(conT ''[] `appT` conT ''Int) g = [] }}} You'll get some unsavory output: {{{ Bug.hs:10:8-34: Splicing type conT ''[] `appT` conT ''Int ======> GHC.Types.[] Int Bug.hs:7:8-53: Splicing type conT ''(,) `appT` conT ''Int `appT` conT ''Int ======> GHC.Tuple.(,) Int Int }}} It's unsavory because if you actually try to use the spliced output in Haskell code: {{{#!hs module Bug2 where f :: GHC.Tuple.(,) Int Int f = (1,2) g :: GHC.Types.[] Int g = [] }}} Then it won't parse. Expressions have the same problem: {{{#!hs {-# LANGUAGE TemplateHaskell #-} {-# OPTIONS_GHC -ddump-splices #-} module Bug3 where import Language.Haskell.TH f :: (Int, Int) f = $(conE '(,) `appE` litE (integerL 1) `appE` litE (integerL 1)) g :: [Int] g = $(conE '[]) }}} {{{ Bug3.hs:8:7-65: Splicing expression conE '(,) `appE` litE (integerL 1) `appE` litE (integerL 1) ======> (GHC.Tuple.(,) 1) 1 Bug3.hs:11:7-14: Splicing expression conE '[] ======> GHC.Types.[] }}} And patterns: {{{#!hs {-# LANGUAGE TemplateHaskell #-} {-# OPTIONS_GHC -ddump-splices #-} module Bug4 where import Language.Haskell.TH f :: (Int, Int) -> () f $(conP '(,) [litP (integerL 1), litP (integerL 1)]) = () g :: [Int] -> () g $(conP '[] []) = () }}} {{{ Bug4.hs:8:5-52: Splicing pattern conP '(,) [litP (integerL 1), litP (integerL 1)] ======> GHC.Tuple.(,) 1 1 Bug4.hs:11:5-15: Splicing pattern conP '[] [] ======> GHC.Types.[] }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jun 1 20:54:01 2017 From: ghc-devs at haskell.org (GHC) Date: Thu, 01 Jun 2017 20:54:01 -0000 Subject: [GHC] #13767: GHCi trips -DS checks at rts/sm/Sanity.c, line 210 In-Reply-To: <046.e0bf705a7b0da22195c9831465099e74@haskell.org> References: <046.e0bf705a7b0da22195c9831465099e74@haskell.org> Message-ID: <061.fe1969243f2d6aa332ff478888b2e808@haskell.org> #13767: GHCi trips -DS checks at rts/sm/Sanity.c, line 210 -------------------------------------+------------------------------------- Reporter: niteria | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Runtime System | Version: 8.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by niteria): * cc: simonmar (added) Comment: I bisected it to https://phabricator.haskell.org/rGHC394231b301efb6b56654b0a480ab794fe3b7e4db, I guess that makes sense given what it does. cc @simonmar -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jun 1 21:09:53 2017 From: ghc-devs at haskell.org (GHC) Date: Thu, 01 Jun 2017 21:09:53 -0000 Subject: [GHC] #11621: GHC doesn't see () as a Constraint in type family In-Reply-To: <051.2614c189cee6aedf6ce97aadd979fbc3@haskell.org> References: <051.2614c189cee6aedf6ce97aadd979fbc3@haskell.org> Message-ID: <066.dc479b9d1b5c274a4300cd01403c8770@haskell.org> #11621: GHC doesn't see () as a Constraint in type family -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 7.10.1 checker) | Keywords: Resolution: | ConstraintKinds Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #11715 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * keywords: => ConstraintKinds Comment: See also #13742 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jun 1 21:10:34 2017 From: ghc-devs at haskell.org (GHC) Date: Thu, 01 Jun 2017 21:10:34 -0000 Subject: [GHC] #13742: Code using ConstraintKinds needs explicit kind signature with GHC 8.2.1 In-Reply-To: <047.8dc343485a25f502c1d7277dfaedb671@haskell.org> References: <047.8dc343485a25f502c1d7277dfaedb671@haskell.org> Message-ID: <062.4a0385b444af8c5b7b7f89a9cb7cc0d1@haskell.org> #13742: Code using ConstraintKinds needs explicit kind signature with GHC 8.2.1 -------------------------------------+------------------------------------- Reporter: albertov | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.2.1-rc2 checker) | Keywords: Resolution: | ConstraintKinds, KindSignatures Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: #11621 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * related: => #11621 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jun 1 21:27:40 2017 From: ghc-devs at haskell.org (GHC) Date: Thu, 01 Jun 2017 21:27:40 -0000 Subject: [GHC] #13761: Can't create poly-kinded GADT with TypeInType enabled, but can without In-Reply-To: <050.2f1e1c074cee1d6dee365ff75365056c@haskell.org> References: <050.2f1e1c074cee1d6dee365ff75365056c@haskell.org> Message-ID: <065.9bbc5226200749bec8dda09f7e13a7b2@haskell.org> #13761: Can't create poly-kinded GADT with TypeInType enabled, but can without -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.1 checker) | Resolution: invalid | Keywords: TypeInType Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): > I mean something like But is that so different from this? {{{ data T :: k -> * where MkT :: T Int }}} Is a separate kind signature better? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jun 1 21:54:07 2017 From: ghc-devs at haskell.org (GHC) Date: Thu, 01 Jun 2017 21:54:07 -0000 Subject: [GHC] #13757: Are you for or against writing "otherwise" as a keyword? In-Reply-To: <044.a4fc99e00f379531d171337bd3da9d21@haskell.org> References: <044.a4fc99e00f379531d171337bd3da9d21@haskell.org> Message-ID: <059.37db307d4632ae8b521bdd4184e542f7@haskell.org> #13757: Are you for or against writing "otherwise" as a keyword? -------------------------------------+------------------------------------- Reporter: vanto | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Poor/confusing | Unknown/Multiple error message | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by nomeata): I am also in the committee, and I agree with what Richard is saying. There is a process, and the situation has not changed. I may not be more senior than Richard, but I speak with the authority of being the Committee Secretary. Also, judging from previous decisions of the committee, I can already tell you that it has a pretty slim chance of success. Often, online communication is not very helpful when you want to get your idea out, and people will not understand your point. Is there maybe a local Haskell meetup in your area where you could bring your idea forward, to gauge and gather support, and get immediate feedback? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jun 1 22:22:04 2017 From: ghc-devs at haskell.org (GHC) Date: Thu, 01 Jun 2017 22:22:04 -0000 Subject: [GHC] #13772: Cannot put HasCallStack on instances In-Reply-To: <047.d360e3ed5517211c4a279da62bac67fe@haskell.org> References: <047.d360e3ed5517211c4a279da62bac67fe@haskell.org> Message-ID: <062.b09d14360caec5bb509b330bc2bfa270@haskell.org> #13772: Cannot put HasCallStack on instances -------------------------------------+------------------------------------- Reporter: augustss | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): You can put implicit-parameter constraints on the methods, but not on the instance. If the instance had implicit-parameter constraints it'd become voisible exactly where the constraint was solved. So currently it's by design. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jun 1 22:25:09 2017 From: ghc-devs at haskell.org (GHC) Date: Thu, 01 Jun 2017 22:25:09 -0000 Subject: [GHC] #5927: A type-level "implies" constraint on Constraints In-Reply-To: <048.176646aa6f5f9bdf7a2953e1f3bc3e76@haskell.org> References: <048.176646aa6f5f9bdf7a2953e1f3bc3e76@haskell.org> Message-ID: <063.a1ddf63fab09b654830e82a39b89c5a4@haskell.org> #5927: A type-level "implies" constraint on Constraints -------------------------------------+------------------------------------- Reporter: illissius | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 7.4.1 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by Artyom.Kazak): * cc: Artyom.Kazak, int-index (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jun 1 22:37:27 2017 From: ghc-devs at haskell.org (GHC) Date: Thu, 01 Jun 2017 22:37:27 -0000 Subject: [GHC] #13185: haskell-relational-query: ghc: panic! (the 'impossible' happened) In-Reply-To: <052.7cf8871089bbe0aab7ba792447e09946@haskell.org> References: <052.7cf8871089bbe0aab7ba792447e09946@haskell.org> Message-ID: <067.c4b06745f3be673fda28f9413e25db72@haskell.org> #13185: haskell-relational-query: ghc: panic! (the 'impossible' happened) -------------------------------------+------------------------------------- Reporter: LocutusOfBorg | Owner: (none) Type: bug | Status: new Priority: high | Milestone: Component: Compiler | Version: 8.0.2 Resolution: | Keywords: Operating System: Linux | Architecture: | Unknown/Multiple Type of failure: Compile-time | Test Case: build crash or panic | relational-query with ghc 8.0.2 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): So `-fsimpl-tick-factor=100` fails, but `-fsimpl-tick-factor=104` works? If so, I'd suggest just increasing the number. There is nothing magical about 100, it was just a finger stuck in the air. It's a little surprising that it takes more effort than before, but I doubt it's worth forensic investigation. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 2 00:24:06 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 02 Jun 2017 00:24:06 -0000 Subject: [GHC] #13761: Can't create poly-kinded GADT with TypeInType enabled, but can without In-Reply-To: <050.2f1e1c074cee1d6dee365ff75365056c@haskell.org> References: <050.2f1e1c074cee1d6dee365ff75365056c@haskell.org> Message-ID: <065.419fcde48b52a976d11b7a5fbefad650@haskell.org> #13761: Can't create poly-kinded GADT with TypeInType enabled, but can without -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.1 checker) | Resolution: invalid | Keywords: TypeInType Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by goldfire): A separate kind signature will be understood independent of the type definition -- much like how type signatures on functions are understood (and kind-generalized) independently of the body. For example, consider {{{ data Proxy (a :: k) = P data S :: Proxy k -> Type where MkS :: S (P :: Proxy Maybe) }}} What's the type of `k`? Taking the definition into account, we can see that `k :: Type -> Type`. But if we must take the definition into account, then we don't have a CUSK, by definition. Currently, the declaration above causes GHC to complain that `Type -> Type` does not match `k`, as we're using `S` at a different instantiation in its body than in its head (i.e. using polymorphic recursion). Change to {{{ data S :: forall k. Proxy k -> Type where ... }}} and now we get {{{ You have written a *complete user-suppled kind signature*, but the following variable is undetermined: k0 :: * Perhaps add a kind signature. }}} This is quite correct. The declaration looks like it has a CUSK, but really it doesn't. Instead, we can write {{{ data S :: forall (k :: Type -> Type). Proxy k -> Type where ... }}} or {{{ data S :: forall (kk :: Type) (k :: kk). Proxy k -> Type where ... }}} both of which are accepted. Note that these define ''different'' types: the second defines a kind-indexed GADT. The point of all this is that it's incredibly confusing. Much better would be (*) A definition can use polymorphic recursion if it has a standalone type/kind signature. Simple! It works for types and terms. And it's exactly what happens for terms today. Under (*), all the declarations for `S` would be rejected, as none of them have a standalone kind signature. (The proposal will also describe `-XCUSKs`, on by default, that retains the current behavior. This extension will be off by default and deprecated in due course.) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 2 01:54:17 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 02 Jun 2017 01:54:17 -0000 Subject: [GHC] #13777: Poor error message around CUSKs Message-ID: <047.11d027cf313fa6dbfb640c7b49929a8b@haskell.org> #13777: Poor error message around CUSKs -------------------------------------+------------------------------------- Reporter: goldfire | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.1-rc2 Keywords: TypeInType, | Operating System: Unknown/Multiple CUSKs | Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- While typing up comment:7:ticket:13761, I came across a poor error message around CUSKs. {{{ data Proxy (a :: k) = P data S :: forall k. Proxy k -> Type where MkS :: S (P :: Proxy Maybe) }}} produces {{{ You have written a *complete user-suppled kind signature*, but the following variable is undetermined: k0 :: * Perhaps add a kind signature. Inferred kinds of user-written variables: }}} That promised list of the kinds of user-written variables is empty. Either GHC should find something to print (like `k :: k0`, perhaps) or omit the header. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 2 02:15:43 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 02 Jun 2017 02:15:43 -0000 Subject: [GHC] #13776: -ddump-splices produces unnecessarily qualified names for tuple and list types In-Reply-To: <050.87f5b641e82d5f06fa4748e90b74c406@haskell.org> References: <050.87f5b641e82d5f06fa4748e90b74c406@haskell.org> Message-ID: <065.7d7227201bc820ee8076ff72552373af@haskell.org> #13776: -ddump-splices produces unnecessarily qualified names for tuple and list types -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 8.0.1 Resolution: | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by goldfire): How would you like it to behave? Should the pretty-printer look under `ConT` constructors for certain names (tuples, lists, etc) and print out the right thing? I suppose so. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 2 02:19:54 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 02 Jun 2017 02:19:54 -0000 Subject: [GHC] #13776: -ddump-splices produces unnecessarily qualified names for tuple and list types In-Reply-To: <050.87f5b641e82d5f06fa4748e90b74c406@haskell.org> References: <050.87f5b641e82d5f06fa4748e90b74c406@haskell.org> Message-ID: <065.61691138d3ba53e0eed3ebccad5e6aed@haskell.org> #13776: -ddump-splices produces unnecessarily qualified names for tuple and list types -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 8.0.1 Resolution: | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): Replying to [comment:1 goldfire]: > Should the pretty-printer look under `ConT` constructors for certain names (tuples, lists, etc) and print out the right thing? Even better, one might envision changing the `Ppr Name` instance so that special constructors like `[]`, `(,)`, etc. are never printed qualified. After all, they don't make sense to print qualified! -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 2 04:21:55 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 02 Jun 2017 04:21:55 -0000 Subject: [GHC] #5927: A type-level "implies" constraint on Constraints In-Reply-To: <048.176646aa6f5f9bdf7a2953e1f3bc3e76@haskell.org> References: <048.176646aa6f5f9bdf7a2953e1f3bc3e76@haskell.org> Message-ID: <063.839c4417a260d7d5fb55dac95c360245@haskell.org> #5927: A type-level "implies" constraint on Constraints -------------------------------------+------------------------------------- Reporter: illissius | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 7.4.1 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by kosmikus): * cc: kosmikus (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 2 06:39:31 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 02 Jun 2017 06:39:31 -0000 Subject: [GHC] #13535: vector test suite uses excessive memory on GHC 8.2 In-Reply-To: <050.16d8aabc8a5c61d8950e3575a8e4ccd4@haskell.org> References: <050.16d8aabc8a5c61d8950e3575a8e4ccd4@haskell.org> Message-ID: <065.f363cfc0b31c7d64bb85a7431442e4d9@haskell.org> #13535: vector test suite uses excessive memory on GHC 8.2 -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: bgamari Type: bug | Status: new Priority: highest | Milestone: 8.2.1 Component: Compiler | Version: 8.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: #10800 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): I've finally managed to identify the commit that caused this memory spike: 1c4a39d3a8d36803382792ff78b4709794358883 (Prioritise class-level equality costraints). -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 2 07:08:50 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 02 Jun 2017 07:08:50 -0000 Subject: [GHC] #13535: vector test suite uses excessive memory on GHC 8.2 In-Reply-To: <050.16d8aabc8a5c61d8950e3575a8e4ccd4@haskell.org> References: <050.16d8aabc8a5c61d8950e3575a8e4ccd4@haskell.org> Message-ID: <065.56641fe544507c3c05b087c4ca19809e@haskell.org> #13535: vector test suite uses excessive memory on GHC 8.2 -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: bgamari Type: bug | Status: new Priority: highest | Milestone: 8.2.1 Component: Compiler | Version: 8.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: #10800 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): I've also confirmed that reverting 1c4a39d3a8d36803382792ff78b4709794358883 from the current master (d39a3409acd3c40fb018ec1c114f15d3ecef6ef9) makes GHC able to compile the `vector` test suite again, so that is a viable workaround. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 2 07:59:37 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 02 Jun 2017 07:59:37 -0000 Subject: [GHC] #13185: haskell-relational-query: ghc: panic! (the 'impossible' happened) In-Reply-To: <052.7cf8871089bbe0aab7ba792447e09946@haskell.org> References: <052.7cf8871089bbe0aab7ba792447e09946@haskell.org> Message-ID: <067.984ccaed11b6bebf6ca4553f4c2da149@haskell.org> #13185: haskell-relational-query: ghc: panic! (the 'impossible' happened) -------------------------------------+------------------------------------- Reporter: LocutusOfBorg | Owner: (none) Type: bug | Status: new Priority: high | Milestone: Component: Compiler | Version: 8.0.2 Resolution: | Keywords: Operating System: Linux | Architecture: | Unknown/Multiple Type of failure: Compile-time | Test Case: build crash or panic | relational-query with ghc 8.0.2 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by LocutusOfBorg): well, 100 was already a good upper bound, the increase is from 80 to 104, not just 4 ticks -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 2 11:31:46 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 02 Jun 2017 11:31:46 -0000 Subject: [GHC] #13778: explicitly bidirectional patterns should not report Recursive definition" when used in view pattern expression position Message-ID: <048.fda620e420aea7183096bc59fa4898e9@haskell.org> #13778: explicitly bidirectional patterns should not report Recursive definition" when used in view pattern expression position -------------------------------------+------------------------------------- Reporter: heisenbug | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.3 Keywords: | Operating System: Unknown/Multiple PatternSynonyms | Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- Compile this {{{#!hs pattern One <- ((==One) -> True) where One = 1 }}} I get {{{ test.hs:1:1: error: Recursive pattern synonym definition with following bindings: One (defined at test.hs:(1,1)-(1,15)) | Compilation failed. }}} Note that the error is due to the usage in view pattern **expression position**. But for ''explicitly bidirectional'' patterns, there is no recursivity going on. So this usage should be allowed. I am testing with HEAD, but the issue is probably older. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 2 12:05:47 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 02 Jun 2017 12:05:47 -0000 Subject: [GHC] #13757: Are you for or against writing "otherwise" as a keyword? In-Reply-To: <044.a4fc99e00f379531d171337bd3da9d21@haskell.org> References: <044.a4fc99e00f379531d171337bd3da9d21@haskell.org> Message-ID: <059.550251428029955dd9bb597697a845be@haskell.org> #13757: Are you for or against writing "otherwise" as a keyword? -------------------------------------+------------------------------------- Reporter: vanto | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Poor/confusing | Unknown/Multiple error message | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by vanto): Replay to [[span(style=color: #FF0000,nomeata)]] :\\ Maybe you make no effort to understand me?\\ > While I appreciate your search for simplicity in posting proposals here to Trac\\ Goldfire got the wrong ticket by answering.\\ He should have used the {{{#13764}}} ticket instead.\\ Nomeata, you did not look at the ticket title.\\ This ticket is about: {{{Are you for or against writing "otherwise" as a keyword?}}}\\ What else can I do to improve? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 2 12:29:29 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 02 Jun 2017 12:29:29 -0000 Subject: [GHC] #13778: explicitly bidirectional patterns should not report Recursive definition" when used in view pattern expression position In-Reply-To: <048.fda620e420aea7183096bc59fa4898e9@haskell.org> References: <048.fda620e420aea7183096bc59fa4898e9@haskell.org> Message-ID: <063.29a51595a06902b426baee234e4d4d90@haskell.org> #13778: explicitly bidirectional patterns should not report Recursive definition" when used in view pattern expression position -------------------------------------+------------------------------------- Reporter: heisenbug | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.3 Resolution: | Keywords: | PatternSynonyms Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by Iceland_jack): * cc: Iceland_jack (added) Comment: This would be good to have -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 2 12:38:54 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 02 Jun 2017 12:38:54 -0000 Subject: [GHC] #11719: Cannot use higher-rank kinds with type families In-Reply-To: <047.7d1567263c03c83c3feb5d4cd6d08b50@haskell.org> References: <047.7d1567263c03c83c3feb5d4cd6d08b50@haskell.org> Message-ID: <062.32a43ea534f09b84d9d670297690827c@haskell.org> #11719: Cannot use higher-rank kinds with type families -------------------------------------+------------------------------------- Reporter: ocharles | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.4.1 Component: Compiler (Type | Version: 8.0.1-rc2 checker) | Resolution: | Keywords: TypeInType Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: GHC rejects | Test Case: valid program | dependent/should_compile/T11719 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by Iceland_jack): * cc: Iceland_jack (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 2 13:01:10 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 02 Jun 2017 13:01:10 -0000 Subject: [GHC] #13770: HEAD: Type mentioned in error won't show up in pattern signature In-Reply-To: <048.bec77fc784cc04e5720ed5fc2293fddf@haskell.org> References: <048.bec77fc784cc04e5720ed5fc2293fddf@haskell.org> Message-ID: <063.a86b32041dd4d248246a07522f750aa4@haskell.org> #13770: HEAD: Type mentioned in error won't show up in pattern signature -------------------------------------+------------------------------------- Reporter: heisenbug | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by heisenbug): I believe the `r4` unification-variable originates from the two wildcard arguments (https://ghc.haskell.org/trac/ghc/attachment/ticket/13770/T13770.hs#L27) hidden in `Fun{}`. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 2 13:29:54 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 02 Jun 2017 13:29:54 -0000 Subject: [GHC] #13535: vector test suite uses excessive memory on GHC 8.2 In-Reply-To: <050.16d8aabc8a5c61d8950e3575a8e4ccd4@haskell.org> References: <050.16d8aabc8a5c61d8950e3575a8e4ccd4@haskell.org> Message-ID: <065.32f58c8d9c53d8fcf9941423e15420bc@haskell.org> #13535: vector test suite uses excessive memory on GHC 8.2 -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: bgamari Type: bug | Status: new Priority: highest | Milestone: 8.2.1 Component: Compiler | Version: 8.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: #10800 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): Great work Ryan! That is a great hint. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 2 13:32:18 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 02 Jun 2017 13:32:18 -0000 Subject: [GHC] #13535: vector test suite uses excessive memory on GHC 8.2 In-Reply-To: <050.16d8aabc8a5c61d8950e3575a8e4ccd4@haskell.org> References: <050.16d8aabc8a5c61d8950e3575a8e4ccd4@haskell.org> Message-ID: <065.ed6add0eb93962c0e64b32ba0f546169@haskell.org> #13535: vector test suite uses excessive memory on GHC 8.2 -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: bgamari Type: bug | Status: new Priority: highest | Milestone: 8.2.1 Component: Compiler | Version: 8.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: #10800 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): It is a bit surprising to hear that this patch is the culprit, however, as it appears to be solely a typechecker change. Perhaps there is some change in the generated Core which then triggers some latent simplifier bug. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 2 16:27:59 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 02 Jun 2017 16:27:59 -0000 Subject: [GHC] #12499: Support multiple library import libs In-Reply-To: <044.f8a196b5cc44f6576f7ecd4b42c8187e@haskell.org> References: <044.f8a196b5cc44f6576f7ecd4b42c8187e@haskell.org> Message-ID: <059.07a720ac71ca84872af0bc2ad9342fe9@haskell.org> #12499: Support multiple library import libs -------------------------------------+------------------------------------- Reporter: Phyx- | Owner: Phyx- Type: feature request | Status: new Priority: normal | Milestone: 8.4.1 Component: Runtime System | Version: 8.0.1 (Linker) | Resolution: | Keywords: Operating System: Windows | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3513 Wiki Page: | -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"93489cd3b4c1b0d17506a12a9b964c0082ddb7a8/ghc" 93489cd3/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="93489cd3b4c1b0d17506a12a9b964c0082ddb7a8" Better import library support for Windows The import library support added for 7.10.3 was only a partial one. This support was predicated on using file extensions to determine whether or not a library was an import library. It also couldn't handle libraries with multiple dll pointers. This is a rewrite of that patch and fully integrating it into the normal archive parsing and loading routines. This solves a host of issues, among others allowing us to finally use `-lgcc_s`. This also fixes a problem with our previous implementation, where we just loaded the DLL and moved on. Doing this had the potential of using the wrong symbol at resolve time. Say a DLL already loaded (A.dll) has symbol a exported (dependency of another dll perhaps). We find an import library `B.lib` explicitly defining an export of `a`. we load `B.dll` but this gets put after `A.dll`, at resolve time we would use the value from `A` instead of `B` which is what we wanted. Test Plan: ./valide and make test TEST=13606 Reviewers: austin, bgamari, erikd, simonmar Reviewed By: bgamari Subscribers: rwbarton, RyanGlScott, thomie, #ghc_windows_task_force GHC Trac Issues: #13606, #12499, #12498 Differential Revision: https://phabricator.haskell.org/D3513 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 2 16:27:59 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 02 Jun 2017 16:27:59 -0000 Subject: [GHC] #8440: Get rid of the remaining static flags In-Reply-To: <052.744af3e10192bedb98c0b515d9a6cc6d@haskell.org> References: <052.744af3e10192bedb98c0b515d9a6cc6d@haskell.org> Message-ID: <067.24864929ec5b8b8e704a550ed49b2d43@haskell.org> #8440: Get rid of the remaining static flags -------------------------------------+------------------------------------- Reporter: thoughtpolice | Owner: (none) Type: task | Status: patch Priority: normal | Milestone: 8.2.1 Component: Compiler | Version: Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2839, Wiki Page: | Phab:D3615 -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"bf775e9d6895c07f629409ee18503f40730cb5a0/ghc" bf775e9/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="bf775e9d6895c07f629409ee18503f40730cb5a0" Remove references to static flags in flag reference A follow-up to #8440 (Ditch static flags). There are still some lingering references to static flags in the flag reference, so let's modify those references accordingly. Test Plan: Build the documentation Reviewers: bgamari, austin Reviewed By: bgamari Subscribers: rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D3615 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 2 16:27:59 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 02 Jun 2017 16:27:59 -0000 Subject: [GHC] #12498: Support unconventionally named import libraries In-Reply-To: <044.5e703c77c226248ade6b1c9ac24961ab@haskell.org> References: <044.5e703c77c226248ade6b1c9ac24961ab@haskell.org> Message-ID: <059.866b6ae06f3b168d9304009fbf863479@haskell.org> #12498: Support unconventionally named import libraries -------------------------------------+------------------------------------- Reporter: Phyx- | Owner: Phyx- Type: feature request | Status: patch Priority: normal | Milestone: 8.4.1 Component: Runtime System | Version: 8.0.1 (Linker) | Resolution: | Keywords: Operating System: Windows | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #11072 | Differential Rev(s): Phab:D3513 Wiki Page: | -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"93489cd3b4c1b0d17506a12a9b964c0082ddb7a8/ghc" 93489cd3/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="93489cd3b4c1b0d17506a12a9b964c0082ddb7a8" Better import library support for Windows The import library support added for 7.10.3 was only a partial one. This support was predicated on using file extensions to determine whether or not a library was an import library. It also couldn't handle libraries with multiple dll pointers. This is a rewrite of that patch and fully integrating it into the normal archive parsing and loading routines. This solves a host of issues, among others allowing us to finally use `-lgcc_s`. This also fixes a problem with our previous implementation, where we just loaded the DLL and moved on. Doing this had the potential of using the wrong symbol at resolve time. Say a DLL already loaded (A.dll) has symbol a exported (dependency of another dll perhaps). We find an import library `B.lib` explicitly defining an export of `a`. we load `B.dll` but this gets put after `A.dll`, at resolve time we would use the value from `A` instead of `B` which is what we wanted. Test Plan: ./valide and make test TEST=13606 Reviewers: austin, bgamari, erikd, simonmar Reviewed By: bgamari Subscribers: rwbarton, RyanGlScott, thomie, #ghc_windows_task_force GHC Trac Issues: #13606, #12499, #12498 Differential Revision: https://phabricator.haskell.org/D3513 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 2 16:27:59 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 02 Jun 2017 16:27:59 -0000 Subject: [GHC] #13762: TypeInType is not documented in the users' guide flag reference In-Reply-To: <050.78435b52d9dc2514bd12b6fce932038d@haskell.org> References: <050.78435b52d9dc2514bd12b6fce932038d@haskell.org> Message-ID: <065.0148c1e1bc5c324779dd522406f34f33@haskell.org> #13762: TypeInType is not documented in the users' guide flag reference -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: patch Priority: normal | Milestone: Component: Documentation | Version: 8.0.1 Resolution: | Keywords: TypeInType Operating System: Unknown/Multiple | Architecture: Type of failure: Documentation | Unknown/Multiple bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3614 Wiki Page: | -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"d0fb0df349d0e51b2b3f7980a8b1eca80051d67f/ghc" d0fb0df3/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="d0fb0df349d0e51b2b3f7980a8b1eca80051d67f" Add a flag reference entry for -XTypeInType Test Plan: Read it Reviewers: bgamari, austin Reviewed By: bgamari Subscribers: rwbarton, thomie GHC Trac Issues: #13762 Differential Revision: https://phabricator.haskell.org/D3614 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 2 16:27:59 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 02 Jun 2017 16:27:59 -0000 Subject: [GHC] #13606: GHCi segfaults on Windows with D3D code In-Reply-To: <050.af5542bb296b21a9acc9021e3f18425a@haskell.org> References: <050.af5542bb296b21a9acc9021e3f18425a@haskell.org> Message-ID: <065.95d4bf00e00f68be194fc8be90db2406@haskell.org> #13606: GHCi segfaults on Windows with D3D code ----------------------------------+---------------------------------------- Reporter: RyanGlScott | Owner: Phyx- Type: bug | Status: patch Priority: normal | Milestone: 8.4.1 Component: GHCi | Version: 8.2.1-rc2 Resolution: | Keywords: Operating System: Windows | Architecture: Unknown/Multiple Type of failure: GHCi crash | Test Case: Blocked By: | Blocking: Related Tickets: #12499 #12498 | Differential Rev(s): Phab:D3513 Wiki Page: | ----------------------------------+---------------------------------------- Comment (by Ben Gamari ): In [changeset:"93489cd3b4c1b0d17506a12a9b964c0082ddb7a8/ghc" 93489cd3/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="93489cd3b4c1b0d17506a12a9b964c0082ddb7a8" Better import library support for Windows The import library support added for 7.10.3 was only a partial one. This support was predicated on using file extensions to determine whether or not a library was an import library. It also couldn't handle libraries with multiple dll pointers. This is a rewrite of that patch and fully integrating it into the normal archive parsing and loading routines. This solves a host of issues, among others allowing us to finally use `-lgcc_s`. This also fixes a problem with our previous implementation, where we just loaded the DLL and moved on. Doing this had the potential of using the wrong symbol at resolve time. Say a DLL already loaded (A.dll) has symbol a exported (dependency of another dll perhaps). We find an import library `B.lib` explicitly defining an export of `a`. we load `B.dll` but this gets put after `A.dll`, at resolve time we would use the value from `A` instead of `B` which is what we wanted. Test Plan: ./valide and make test TEST=13606 Reviewers: austin, bgamari, erikd, simonmar Reviewed By: bgamari Subscribers: rwbarton, RyanGlScott, thomie, #ghc_windows_task_force GHC Trac Issues: #13606, #12499, #12498 Differential Revision: https://phabricator.haskell.org/D3513 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 2 16:27:59 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 02 Jun 2017 16:27:59 -0000 Subject: [GHC] #13385: ghci fails to start when -XRebindableSyntax is passed In-Reply-To: <046.49534d46a543f72893ed665a08de1bb0@haskell.org> References: <046.49534d46a543f72893ed665a08de1bb0@haskell.org> Message-ID: <061.2b4458c64a70c4927a9147bcb335e641@haskell.org> #13385: ghci fails to start when -XRebindableSyntax is passed -------------------------------------+------------------------------------- Reporter: mgsloan | Owner: (none) Type: bug | Status: patch Priority: normal | Milestone: Component: GHCi | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3621 Wiki Page: | -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"2abe54e16cbd14cab27abdc7967e907753354d54/ghc" 2abe54e1/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="2abe54e16cbd14cab27abdc7967e907753354d54" Make GHCi work when RebindableSyntax is enabled Previously, we were running some blocks of code at the start of every GHCi sessions which use do-notation, something which doesn't work well if you start GHCi with the `-XRebindableSyntax` flag on. This tweaks the code to avoid the use of do-notation so that `-XRebindableSyntax` won't reject it. Test Plan: make test TEST=T13385 Reviewers: austin, bgamari Reviewed By: bgamari Subscribers: rwbarton, thomie GHC Trac Issues: #13385 Differential Revision: https://phabricator.haskell.org/D3621 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 2 16:28:45 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 02 Jun 2017 16:28:45 -0000 Subject: [GHC] #13762: TypeInType is not documented in the users' guide flag reference In-Reply-To: <050.78435b52d9dc2514bd12b6fce932038d@haskell.org> References: <050.78435b52d9dc2514bd12b6fce932038d@haskell.org> Message-ID: <065.9d5063f2b6859927b7dd448578359d8b@haskell.org> #13762: TypeInType is not documented in the users' guide flag reference -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.2.1 Component: Documentation | Version: 8.0.1 Resolution: fixed | Keywords: TypeInType Operating System: Unknown/Multiple | Architecture: Type of failure: Documentation | Unknown/Multiple bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3614 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: patch => closed * resolution: => fixed * milestone: => 8.2.1 Comment: Also pulled to `ghc-8.2`. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 2 16:29:41 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 02 Jun 2017 16:29:41 -0000 Subject: [GHC] #12499: Support multiple library import libs In-Reply-To: <044.f8a196b5cc44f6576f7ecd4b42c8187e@haskell.org> References: <044.f8a196b5cc44f6576f7ecd4b42c8187e@haskell.org> Message-ID: <059.55fceec30f931c2dc6a4ba5a46ccbcbe@haskell.org> #12499: Support multiple library import libs -------------------------------------+------------------------------------- Reporter: Phyx- | Owner: Phyx- Type: feature request | Status: closed Priority: normal | Milestone: 8.4.1 Component: Runtime System | Version: 8.0.1 (Linker) | Resolution: fixed | Keywords: Operating System: Windows | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3513 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => closed * resolution: => fixed -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 2 16:30:46 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 02 Jun 2017 16:30:46 -0000 Subject: [GHC] #13606: GHCi segfaults on Windows with D3D code In-Reply-To: <050.af5542bb296b21a9acc9021e3f18425a@haskell.org> References: <050.af5542bb296b21a9acc9021e3f18425a@haskell.org> Message-ID: <065.18abbfad570fc3d0c3f39c1fba0779a0@haskell.org> #13606: GHCi segfaults on Windows with D3D code ----------------------------------+---------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.4.1 Component: GHCi | Version: 8.2.1-rc2 Resolution: | Keywords: Operating System: Windows | Architecture: Unknown/Multiple Type of failure: GHCi crash | Test Case: Blocked By: | Blocking: Related Tickets: #12499 #12498 | Differential Rev(s): Phab:D3513 Wiki Page: | ----------------------------------+---------------------------------------- Changes (by bgamari): * owner: Phyx- => (none) * status: patch => new Comment: RyanGlScott, can you confirm that this fixes the issue? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 2 16:31:18 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 02 Jun 2017 16:31:18 -0000 Subject: [GHC] #13385: ghci fails to start when -XRebindableSyntax is passed In-Reply-To: <046.49534d46a543f72893ed665a08de1bb0@haskell.org> References: <046.49534d46a543f72893ed665a08de1bb0@haskell.org> Message-ID: <061.8410e24b5e70c1b8d970943007659e14@haskell.org> #13385: ghci fails to start when -XRebindableSyntax is passed -------------------------------------+------------------------------------- Reporter: mgsloan | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.4.1 Component: GHCi | Version: 8.0.1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3621 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: patch => closed * resolution: => fixed * milestone: => 8.4.1 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 2 16:37:25 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 02 Jun 2017 16:37:25 -0000 Subject: [GHC] #13779: Add more signature suppression control for dumps Message-ID: <045.b44ddd36d0c9b6a6e5b4023b72336dc3@haskell.org> #13779: Add more signature suppression control for dumps -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: (none) Type: feature | Status: new request | Priority: normal | Milestone: 8.4.1 Component: Compiler | Version: 8.2.1-rc2 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- I tend to find some type signatures essential when reading Core. However, `Generic`-heavy code can produce extremely large signatures. I suspect one or both of the following additional options could help: 1. An option to suppress non-top-level signatures, leaving top-level ones alone. 2. An option to suppress phantom type arguments in signatures. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 2 16:37:49 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 02 Jun 2017 16:37:49 -0000 Subject: [GHC] #13739: Very slow linking of profiled executables In-Reply-To: <043.2d2650cd128632597774b5afb6c7a225@haskell.org> References: <043.2d2650cd128632597774b5afb6c7a225@haskell.org> Message-ID: <058.acd07c603d0b47abd70d7cc7d68a32bd@haskell.org> #13739: Very slow linking of profiled executables -------------------------------------+------------------------------------- Reporter: duog | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.1-rc2 Resolution: | Keywords: Operating System: Linux | Architecture: x86_64 Type of failure: Compile-time | (amd64) performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): Really, you don't even need profiled code to notice a difference. On my machine with `gcc-4.8.4`/`ld-2.24`, I experience longer linking times with an ordinary, non-profiled `main=return ()` executable: {{{ $ time /opt/ghc/8.0.2/bin/ghc -fforce-recomp -O0 Bug.hs [1 of 1] Compiling Main ( Bug.hs, Bug.o ) Linking Bug ... real 0m0.441s user 0m0.360s sys 0m0.060s $ time /opt/ghc/8.2.1/bin/ghc -fforce-recomp -O0 Bug.hs [1 of 1] Compiling Main ( Bug.hs, Bug.o ) Linking Bug ... real 0m1.616s user 0m1.476s sys 0m0.116s }}} On larger programs, the delay is more noticeable. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 2 17:11:09 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 02 Jun 2017 17:11:09 -0000 Subject: [GHC] #8440: Get rid of the remaining static flags In-Reply-To: <052.744af3e10192bedb98c0b515d9a6cc6d@haskell.org> References: <052.744af3e10192bedb98c0b515d9a6cc6d@haskell.org> Message-ID: <067.aa00734cec2d1cd830a63baf2e960f0e@haskell.org> #8440: Get rid of the remaining static flags -------------------------------------+------------------------------------- Reporter: thoughtpolice | Owner: (none) Type: task | Status: closed Priority: normal | Milestone: 8.2.1 Component: Compiler | Version: Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2839, Wiki Page: | Phab:D3615 -------------------------------------+------------------------------------- Changes (by bgamari): * status: patch => closed * resolution: => fixed -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 2 17:11:25 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 02 Jun 2017 17:11:25 -0000 Subject: [GHC] #12498: Support unconventionally named import libraries In-Reply-To: <044.5e703c77c226248ade6b1c9ac24961ab@haskell.org> References: <044.5e703c77c226248ade6b1c9ac24961ab@haskell.org> Message-ID: <059.27423ad0cf0ba834dd8ef17deb90ad2a@haskell.org> #12498: Support unconventionally named import libraries -------------------------------------+------------------------------------- Reporter: Phyx- | Owner: Phyx- Type: feature request | Status: closed Priority: normal | Milestone: 8.4.1 Component: Runtime System | Version: 8.0.1 (Linker) | Resolution: fixed | Keywords: Operating System: Windows | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #11072 | Differential Rev(s): Phab:D3513 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: patch => closed * resolution: => fixed -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 2 18:02:15 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 02 Jun 2017 18:02:15 -0000 Subject: [GHC] #12545: Compilation time/space regression in GHC 8.0/8.1 (search in type-level lists and -O) In-Reply-To: <057.9aecaec89b7fd255565e55bac0801cc6@haskell.org> References: <057.9aecaec89b7fd255565e55bac0801cc6@haskell.org> Message-ID: <072.308903bf51ac2fa9d5aa7685f03031c3@haskell.org> #12545: Compilation time/space regression in GHC 8.0/8.1 (search in type-level lists and -O) -------------------------------------+------------------------------------- Reporter: | Owner: (none) mikhail.vorozhtsov | Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Inlining Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"a786b136f48dfcf907dad55bcdbc4fcd247f2794/ghc" a786b136/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="a786b136f48dfcf907dad55bcdbc4fcd247f2794" Use lengthIs and friends in more places While investigating #12545, I discovered several places in the code that performed length-checks like so: ``` length ts == 4 ``` This is not ideal, since the length of `ts` could be much longer than 4, and we'd be doing way more work than necessary! There are already a slew of helper functions in `Util` such as `lengthIs` that are designed to do this efficiently, so I found every place where they ought to be used and did just that. I also defined a couple more utility functions for list length that were common patterns (e.g., `ltLength`). Test Plan: ./validate Reviewers: austin, hvr, goldfire, bgamari, simonmar Reviewed By: bgamari, simonmar Subscribers: goldfire, rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D3622 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 2 18:08:11 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 02 Jun 2017 18:08:11 -0000 Subject: [GHC] #9630: compile-time performance regression (probably due to Generics) In-Reply-To: <042.a529e5f70870528e7f8796a28ce82a84@haskell.org> References: <042.a529e5f70870528e7f8796a28ce82a84@haskell.org> Message-ID: <057.47bdc59fee1f6dbd03e8897e11df3872@haskell.org> #9630: compile-time performance regression (probably due to Generics) -------------------------------------+------------------------------------- Reporter: hvr | Owner: dfeuer Type: bug | Status: new Priority: high | Milestone: 8.2.1 Component: Compiler | Version: 7.9 Resolution: | Keywords: deriving- | perf, Generics Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: #9583, #10293, | Differential Rev(s): #13059, #10818 | Wiki Page: | -------------------------------------+------------------------------------- Comment (by dfeuer): I pored over `-ddump-ds`, and I think I see what's going on. Suppose we have (cereal-style, but without any `INLINE`s) {{{#!hs class Serialize t where put :: Putter t get :: Get t default put :: (Generic t, GSerialize (Rep t)) => Putter t put = gPut . from default get :: (Generic t, GSerialize (Rep t)) => Get t get = to <$> gGet data T = T () () () () () deriving Generic instance Serialize T }}} What we want to do is build a single `GSerialize (Rep T)` dictionary and share it between `put` and `get`. But when we desugar `instance Serialize T`, we end up building a `GSerialize (Rep T)` dictionary in the definition of `put` and ''another one'' in the definition of `get`. The problem even occurs without `DefaultSignatures`; writing the instance by hand using `gPut` and `gGet` is sufficient to demonstrate the problem: {{{#!hs instance Serialize T where put = gPut . from get = to <$> gGet }}} bgamari indicates that instances are supposed to be cached. Indeed, if I write {{{#!hs putT :: Putter T putT = gPut . from getT :: Get T getT = to <$> gGet }}} at the top level, then all is well. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 2 18:51:06 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 02 Jun 2017 18:51:06 -0000 Subject: [GHC] #13779: Add more signature suppression control for dumps In-Reply-To: <045.b44ddd36d0c9b6a6e5b4023b72336dc3@haskell.org> References: <045.b44ddd36d0c9b6a6e5b4023b72336dc3@haskell.org> Message-ID: <060.5f5b4eadd3bba0cb79cec17aa2a4818e@haskell.org> #13779: Add more signature suppression control for dumps -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: 8.4.1 Component: Compiler | Version: 8.2.1-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by goldfire): What do you mean by signature here? Can you give an example of what you'd like the flag to do? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 2 19:01:07 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 02 Jun 2017 19:01:07 -0000 Subject: [GHC] #13779: Add more signature suppression control for dumps In-Reply-To: <045.b44ddd36d0c9b6a6e5b4023b72336dc3@haskell.org> References: <045.b44ddd36d0c9b6a6e5b4023b72336dc3@haskell.org> Message-ID: <060.fed5bf693f65ddaa2c874ed885c20148@haskell.org> #13779: Add more signature suppression control for dumps -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: 8.4.1 Component: Compiler | Version: 8.2.1-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): I suspect David wants a flag to omit type signatures from let-bindings but retain them for top-levels. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 2 19:07:35 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 02 Jun 2017 19:07:35 -0000 Subject: [GHC] #13779: Add more signature suppression control for dumps In-Reply-To: <045.b44ddd36d0c9b6a6e5b4023b72336dc3@haskell.org> References: <045.b44ddd36d0c9b6a6e5b4023b72336dc3@haskell.org> Message-ID: <060.0c58e0bc0aec4c69dd144d8f914d040c@haskell.org> #13779: Add more signature suppression control for dumps -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: 8.4.1 Component: Compiler | Version: 8.2.1-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by dfeuer): I mostly want to be able to suppress them in function arguments. `\(x :: HUGE TYPE). ...`. Being able to suppress them in `let` bindings separately wouldn't be bad either. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 2 20:08:44 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 02 Jun 2017 20:08:44 -0000 Subject: [GHC] #9630: compile-time performance regression (probably due to Generics) In-Reply-To: <042.a529e5f70870528e7f8796a28ce82a84@haskell.org> References: <042.a529e5f70870528e7f8796a28ce82a84@haskell.org> Message-ID: <057.f59178b0f333e36b58fdeb945d08f95b@haskell.org> #9630: compile-time performance regression (probably due to Generics) -------------------------------------+------------------------------------- Reporter: hvr | Owner: dfeuer Type: bug | Status: new Priority: high | Milestone: 8.2.1 Component: Compiler | Version: 7.9 Resolution: | Keywords: deriving- | perf, Generics Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: #9583, #10293, | Differential Rev(s): #13059, #10818 | Wiki Page: | -------------------------------------+------------------------------------- Comment (by dfeuer): Here's a truly bare-bones, Haskell 98 reproduction: {{{#!hs module Duh where class Duh a where duh :: Integer -> a noDuh :: a -> Integer class GenDuh a where gduh :: Integer -> a gnoDuh :: a -> Integer instance GenDuh () where gduh = const () gnoDuh = const 1 instance GenDuh a => GenDuh (Maybe a) where gduh 0 = Nothing gduh n = Just (gduh (n - 1)) gnoDuh Nothing = 0 gnoDuh (Just x) = 1 + gnoDuh x data T = T (Maybe (Maybe ())) instance Duh T where duh i = T (gduh i) noDuh (T m) = gnoDuh m }}} GHC 8.2.1rc2 with `-O2 -ddump-ds` produces {{{ -- RHS size: {terms: 13, types: 18, coercions: 0, joins: 0/2} $cnoDuh_aRo :: T -> Integer [LclId] $cnoDuh_aRo = let { $dGenDuh_a2nn :: GenDuh (Maybe ()) [LclId] $dGenDuh_a2nn = Duh.$fGenDuhMaybe @ () Duh.$fGenDuh() } in let { $dGenDuh_aRs :: GenDuh (Maybe (Maybe ())) [LclId] $dGenDuh_aRs = Duh.$fGenDuhMaybe @ (Maybe ()) $dGenDuh_a2nn } in \ (ds_d2ow :: T) -> case ds_d2ow of { T m_azN -> gnoDuh @ (Maybe (Maybe ())) $dGenDuh_aRs m_azN } -- RHS size: {terms: 11, types: 14, coercions: 0, joins: 0/2} $cduh_aRi :: Integer -> T [LclId] $cduh_aRi = let { $dGenDuh_a2nl :: GenDuh (Maybe ()) [LclId] $dGenDuh_a2nl = Duh.$fGenDuhMaybe @ () Duh.$fGenDuh() } in let { $dGenDuh_aRm :: GenDuh (Maybe (Maybe ())) [LclId] $dGenDuh_aRm = Duh.$fGenDuhMaybe @ (Maybe ()) $dGenDuh_a2nl } in \ (i_azM :: Integer) -> Duh.T (gduh @ (Maybe (Maybe ())) $dGenDuh_aRm i_azM) }}} We solve the `GenDuh (Maybe (Maybe ()))` constraint twice, and build its dictionary twice. I'll attach `-ddump-tc-trace`. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 2 20:13:53 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 02 Jun 2017 20:13:53 -0000 Subject: [GHC] #9630: compile-time performance regression (probably due to Generics) In-Reply-To: <042.a529e5f70870528e7f8796a28ce82a84@haskell.org> References: <042.a529e5f70870528e7f8796a28ce82a84@haskell.org> Message-ID: <057.96c5b179aeb21855616d8b4045e74d9d@haskell.org> #9630: compile-time performance regression (probably due to Generics) -------------------------------------+------------------------------------- Reporter: hvr | Owner: dfeuer Type: bug | Status: new Priority: high | Milestone: 8.2.1 Component: Compiler | Version: 7.9 Resolution: | Keywords: deriving- | perf, Generics Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: #9583, #10293, | Differential Rev(s): #13059, #10818 | Wiki Page: | -------------------------------------+------------------------------------- Changes (by dfeuer): * Attachment "tracetcduh" added. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 2 20:14:07 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 02 Jun 2017 20:14:07 -0000 Subject: [GHC] #9630: compile-time performance regression (probably due to Generics) In-Reply-To: <042.a529e5f70870528e7f8796a28ce82a84@haskell.org> References: <042.a529e5f70870528e7f8796a28ce82a84@haskell.org> Message-ID: <057.26d9555d2acfb825a45259685729e59c@haskell.org> #9630: compile-time performance regression (probably due to Generics) -------------------------------------+------------------------------------- Reporter: hvr | Owner: dfeuer Type: bug | Status: new Priority: high | Milestone: 8.2.1 Component: Compiler | Version: 7.9 Resolution: | Keywords: deriving- | perf, Generics Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: #9583, #10293, | Differential Rev(s): #13059, #10818 | Wiki Page: | -------------------------------------+------------------------------------- Changes (by dfeuer): * Attachment "tracecsduh" added. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 2 20:54:05 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 02 Jun 2017 20:54:05 -0000 Subject: [GHC] #13780: Nightmarish pretty-printing of equality type in GHC 8.2 error message Message-ID: <050.1bf0abe11448fb7d29d255c23fc5b878@haskell.org> #13780: Nightmarish pretty-printing of equality type in GHC 8.2 error message -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.1-rc2 (Type checker) | Keywords: TypeInType | Operating System: Unknown/Multiple Architecture: | Type of failure: Poor/confusing Unknown/Multiple | error message Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- I originally spotted this in https://ghc.haskell.org/trac/ghc/ticket/12102#comment:1, but I happened to stumble upon it again recently in a separate context, so I though it deserved its own ticket. Here's some code which does not typecheck: {{{#!hs {-# LANGUAGE ExistentialQuantification #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE TypeInType #-} module Foo where data family Sing (a :: k) data Foo a = a ~ Bool => MkFoo data instance Sing (z :: Foo a) = (z ~ MkFoo) => SMkFoo }}} In GHC 8.0.1 and 8.0.2, the error message you'd get from this program was reasonable enough: {{{ GHCi, version 8.0.2: http://www.haskell.org/ghc/ :? for help Loaded GHCi configuration from /home/rgscott/.ghci [1 of 1] Compiling Foo ( Bug.hs, interpreted ) Bug.hs:9:40: error: • Expected kind ‘Foo a’, but ‘'MkFoo’ has kind ‘Foo Bool’ • In the second argument of ‘~’, namely ‘MkFoo’ In the definition of data constructor ‘SMkFoo’ In the data instance declaration for ‘Sing’ }}} But in GHC 8.2.1 and HEAD, it's hair-raisingly bad: {{{ GHCi, version 8.2.0.20170522: http://www.haskell.org/ghc/ :? for help Loaded GHCi configuration from /home/rgscott/.ghci [1 of 1] Compiling Foo ( Bug.hs, interpreted ) Bug.hs:9:40: error: • Expected kind ‘Foo a’, but ‘'MkFoo ('Data.Type.Equality.C:~ ('GHC.Types.Eq# <>))’ has kind ‘Foo Bool’ • In the second argument of ‘~’, namely ‘MkFoo’ In the definition of data constructor ‘SMkFoo’ In the data instance declaration for ‘Sing’ | 9 | data instance Sing (z :: Foo a) = (z ~ MkFoo) => SMkFoo | ^^^^^ }}} **WAT.** -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 2 21:09:41 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 02 Jun 2017 21:09:41 -0000 Subject: [GHC] #13766: Confusing "redundant pattern match" in 8.0, no warning at all in 8.2 In-Reply-To: <044.a0d4ddde4ac467954a614a3fdf55fb65@haskell.org> References: <044.a0d4ddde4ac467954a614a3fdf55fb65@haskell.org> Message-ID: <059.dc972ae1a258501768d2d010596a6b56@haskell.org> #13766: Confusing "redundant pattern match" in 8.0, no warning at all in 8.2 -------------------------------------+------------------------------------- Reporter: edsko | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): I talked with mpickering about this privately, but I'll recap the conversation here as well. This may be expected behavior the sense of comment:5, but I still find it unsettling. The code that adb565aa74582969bbcc3b411d6d518b1c76c3cf targeted was of the form: {{{#!hs f = case [] of (_:_) -> case () of a -> undefined }}} Here, it'll warn that the `(_:_)` match is redundant: {{{ Pattern match is redundant In a case alternative: (_ : _) -> ... }}} And thanks to the aforementioned commit, it will //not// warn about the inaccessible `a -> undefined` case. This is definitely a Good Thing. A similar scenario arises in the code in this example: {{{#!hs instance Int ~ Bool => C Int where c = id }}} Because `Int ~ Bool` is insoluble (and thus all the code inside the instance is inaccessible), it won't bother printing out a warning that `c` is inaccessible. But this is a tad skeevy. In the former example, there was a separate warning that hinted that you were doing something questionable. In the latter example, however, there's no warning at all to point out the dubious nature of your code! Therefore, I think a satisfactory conclusion to this bug would be to come up with a suitable warning about the `Int ~ Bool` constraint. Whether that's the purview of #12694 or some other ticket, I'm not sure. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 2 21:51:45 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 02 Jun 2017 21:51:45 -0000 Subject: [GHC] #13779: Add more signature suppression control for dumps In-Reply-To: <045.b44ddd36d0c9b6a6e5b4023b72336dc3@haskell.org> References: <045.b44ddd36d0c9b6a6e5b4023b72336dc3@haskell.org> Message-ID: <060.90655d6c193cc142ecfc967254b2b070@haskell.org> #13779: Add more signature suppression control for dumps -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: 8.4.1 Component: Compiler | Version: 8.2.1-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): For what it's worth, I have a rather under-advertised GHC core-to-core [[http://github.com/bgamari/ghc-dump|plugin]] which dumps Core to a file in machine-readable form for later inspection. There are also tools for, among other things, pretty-printing the files in the human-readable(?) form we all love in addition to a library allowing you to inspect the representation in GHCi. This is nice for a variety of reasons, * You have more control over what bits to show * You can start with a minimal dump of the program and then decide to show more details later without recompiling your program * You can easily search for bindings by name, type, etc. * Other nice reasons that this margin is too small to contain One feature it currently misses that I would love is the ability to diff files up to alpha-equivalence. However, I feel like this advertisement has gone on for too long already. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 2 21:54:37 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 02 Jun 2017 21:54:37 -0000 Subject: [GHC] #13781: (a :: (k :: Type)) is too exotic for Template Haskell Message-ID: <050.7f27300750c1a83b8949d3702d68d5eb@haskell.org> #13781: (a :: (k :: Type)) is too exotic for Template Haskell -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Template | Version: 8.0.1 Haskell | Keywords: TypeInType | Operating System: Unknown/Multiple Architecture: | Type of failure: GHC rejects Unknown/Multiple | valid program Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- On GHC 8.0.1 or later, GHC will choke on this code: {{{#!hs {-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE TypeInType #-} module Bug where import Data.Kind import Data.Proxy $([d| f :: Proxy (a :: (k :: Type)) f = Proxy |]) }}} {{{ GHCi, version 8.2.0.20170522: http://www.haskell.org/ghc/ :? for help Loaded GHCi configuration from /home/rgscott/.ghci [1 of 1] Compiling Bug ( Bug.hs, interpreted ) Bug.hs:8:3: error: Exotic form of kind not (yet) handled by Template Haskell (k :: Type) | 8 | $([d| f :: Proxy (a :: (k :: Type)) | ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^... }}} I don't think this would be too hard to support, though. I'll take a shot at fixing this. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 2 21:54:48 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 02 Jun 2017 21:54:48 -0000 Subject: [GHC] #13781: (a :: (k :: Type)) is too exotic for Template Haskell In-Reply-To: <050.7f27300750c1a83b8949d3702d68d5eb@haskell.org> References: <050.7f27300750c1a83b8949d3702d68d5eb@haskell.org> Message-ID: <065.1c982794deea90cbef53bbf17225c189@haskell.org> #13781: (a :: (k :: Type)) is too exotic for Template Haskell -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: RyanGlScott Type: bug | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 8.0.1 Resolution: | Keywords: TypeInType Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * owner: (none) => RyanGlScott -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 2 22:40:47 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 02 Jun 2017 22:40:47 -0000 Subject: [GHC] #11032: Missing result type handling for State# s in foreign import prim. In-Reply-To: <045.864636ea7945cdc0bca5fad7c6cfe665@haskell.org> References: <045.864636ea7945cdc0bca5fad7c6cfe665@haskell.org> Message-ID: <060.012902f1d571419bb31440013c16da02@haskell.org> #11032: Missing result type handling for State# s in foreign import prim. -------------------------------------+------------------------------------- Reporter: ekmett | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (FFI) | Version: 7.10.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: #9352 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * related: => #9352 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 2 22:40:58 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 02 Jun 2017 22:40:58 -0000 Subject: [GHC] #9352: Allow `State# s` argument/result types in `ccall` FFI imports In-Reply-To: <042.badab7c0b70bc218549980e1ff162223@haskell.org> References: <042.badab7c0b70bc218549980e1ff162223@haskell.org> Message-ID: <057.367ed70ec0f487f629b43485008f76c8@haskell.org> #9352: Allow `State# s` argument/result types in `ccall` FFI imports -------------------------------------+------------------------------------- Reporter: hvr | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 7.8.2 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #9281, #11032 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * related: #9281 => #9281, #11032 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 2 22:41:11 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 02 Jun 2017 22:41:11 -0000 Subject: [GHC] #11032: Missing result type handling for State# s in foreign import prim. In-Reply-To: <045.864636ea7945cdc0bca5fad7c6cfe665@haskell.org> References: <045.864636ea7945cdc0bca5fad7c6cfe665@haskell.org> Message-ID: <060.5374b7929e6f7a1a4f373829d1a8e013@haskell.org> #11032: Missing result type handling for State# s in foreign import prim. -------------------------------------+------------------------------------- Reporter: ekmett | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler (FFI) | Version: 7.10.2 Resolution: duplicate | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: #9352 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => closed * resolution: => duplicate -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 2 22:43:30 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 02 Jun 2017 22:43:30 -0000 Subject: [GHC] #13781: (a :: (k :: Type)) is too exotic for Template Haskell In-Reply-To: <050.7f27300750c1a83b8949d3702d68d5eb@haskell.org> References: <050.7f27300750c1a83b8949d3702d68d5eb@haskell.org> Message-ID: <065.b06ad715aadc136724396eeee102e6ef@haskell.org> #13781: (a :: (k :: Type)) is too exotic for Template Haskell -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: RyanGlScott Type: bug | Status: patch Priority: normal | Milestone: Component: Template Haskell | Version: 8.0.1 Resolution: | Keywords: TypeInType Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3627 Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * status: new => patch * differential: => Phab:D3627 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 2 23:18:54 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 02 Jun 2017 23:18:54 -0000 Subject: [GHC] #9630: compile-time performance regression (probably due to Generics) In-Reply-To: <042.a529e5f70870528e7f8796a28ce82a84@haskell.org> References: <042.a529e5f70870528e7f8796a28ce82a84@haskell.org> Message-ID: <057.ffa224d26ae145a03dcbd5478cf734f5@haskell.org> #9630: compile-time performance regression (probably due to Generics) -------------------------------------+------------------------------------- Reporter: hvr | Owner: dfeuer Type: bug | Status: new Priority: high | Milestone: 8.2.1 Component: Compiler | Version: 7.9 Resolution: | Keywords: deriving- | perf, Generics Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: #9583, #10293, | Differential Rev(s): #13059, #10818 | Wiki Page: | -------------------------------------+------------------------------------- Comment (by dfeuer): My `Duh` test case appears to go bad in 32973bf3c2f6fe00e01b44a63ac1904080466938 ("Major patch to add -fwarn- redundant-constraints"). -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 2 23:19:14 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 02 Jun 2017 23:19:14 -0000 Subject: [GHC] #13782: Bullish use of Template Haskell's newName causes GHC internal error Message-ID: <050.355b0f2ffb6750de858fbc3a1ccc85be@haskell.org> #13782: Bullish use of Template Haskell's newName causes GHC internal error -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Template | Version: 8.0.1 Haskell | Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: GHC rejects Unknown/Multiple | valid program Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- int-index originally spotted this bug at https://github.com/goldfirere/singletons/issues/150#issuecomment-305909199. To reproduce, compile this file with GHC 8.0.1, 8.0.2, 8.2.1, or HEAD: {{{#!hs {-# LANGUAGE DataKinds #-} {-# LANGUAGE ExistentialQuantification #-} {-# LANGUAGE PolyKinds #-} {-# LANGUAGE TemplateHaskell #-} module Bug where import Language.Haskell.TH $(do TyConI (DataD _ _ [KindedTV a1 _] _ _ _) <- reify ''Maybe [f,a2] <- mapM newName ["f","a"] return [ SigD f (ForallT [KindedTV a2 (AppT (ConT ''Maybe) (VarT a1))] [] (ConT ''Int)) , ValD (VarP f) (NormalB (LitE (IntegerL 42))) [] ]) }}} {{{ GHCi, version 8.2.0.20170522: http://www.haskell.org/ghc/ :? for help Loaded GHCi configuration from /home/rgscott/.ghci [1 of 1] Compiling Bug ( Bug.hs, interpreted ) Bug.hs:9:3: error: • GHC internal error: ‘a_11’ is not in scope during type checking, but it passed the renamer tcl_env of environment: [] • In the first argument of ‘Maybe’, namely ‘a_11’ In the kind ‘Maybe a_11’ In the type signature: f :: forall (a_a4Qz :: Maybe a_11). Int | 9 | $(do TyConI (DataD _ _ [KindedTV a1 _] _ _ _) <- reify ''Maybe | ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^... }}} The root cause of the issue seems to be that the name `a` (which we picked for `newName`) happens to clash with the type variable we reified from `Maybe` (since `data Maybe a = ...`). If we pick a different name: {{{#!hs [f,a2] <- mapM newName ["f","albatross"] }}} Then it will compile. This is a regression from GHC 7.10.3, as it compiles in that version (with a slight change to accommodate the API differences in `DataD` between 7.10.3 and 8.0): {{{#!hs {-# LANGUAGE DataKinds #-} {-# LANGUAGE ExistentialQuantification #-} {-# LANGUAGE PolyKinds #-} {-# LANGUAGE TemplateHaskell #-} module Works where import Language.Haskell.TH $(do TyConI (DataD _ _ [KindedTV a1 _] _ _) <- reify ''Maybe [f,a2] <- mapM newName ["f","a"] return [ SigD f (ForallT [KindedTV a2 (AppT (ConT ''Maybe) (VarT a1))] [] (ConT ''Int)) , ValD (VarP f) (NormalB (LitE (IntegerL 42))) [] ]) }}} {{{ $ /opt/ghc/7.10.3/bin/ghci Works.hs -ddump-splices GHCi, version 7.10.3: http://www.haskell.org/ghc/ :? for help [1 of 1] Compiling Works ( Works.hs, interpreted ) Works.hs:(9,3)-(14,13): Splicing declarations do { TyConI (DataD _ _ [KindedTV a1_a3jt _] _ _) <- reify ''Maybe; [f_a3nh, a2_a3ni] <- mapM newName ["f", "a"]; return [SigD f_a3nh (ForallT [KindedTV a2_a3ni (AppT (ConT ''Maybe) (VarT a1_a3jt))] [] (ConT ''Int)), ValD (VarP f_a3nh) (NormalB (LitE (IntegerL 42))) []] } ======> f_a4vc :: forall (a_a4vd :: Maybe a_a4v3). Int f_a4vc = 42 Ok, modules loaded: Works. }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jun 3 00:07:40 2017 From: ghc-devs at haskell.org (GHC) Date: Sat, 03 Jun 2017 00:07:40 -0000 Subject: [GHC] #12498: Support unconventionally named import libraries In-Reply-To: <044.5e703c77c226248ade6b1c9ac24961ab@haskell.org> References: <044.5e703c77c226248ade6b1c9ac24961ab@haskell.org> Message-ID: <059.9efc5ad8e543b10761ed44c9ea94cc48@haskell.org> #12498: Support unconventionally named import libraries -------------------------------------+------------------------------------- Reporter: Phyx- | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: 8.4.1 Component: Runtime System | Version: 8.0.1 (Linker) | Resolution: | Keywords: Operating System: Windows | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #11072 | Differential Rev(s): Phab:D3513 Wiki Page: | -------------------------------------+------------------------------------- Changes (by Phyx-): * owner: Phyx- => (none) * status: closed => new * resolution: fixed => Comment: The Microsoft format is still detected using extensions. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jun 3 00:07:52 2017 From: ghc-devs at haskell.org (GHC) Date: Sat, 03 Jun 2017 00:07:52 -0000 Subject: [GHC] #12498: Support unconventionally named import libraries In-Reply-To: <044.5e703c77c226248ade6b1c9ac24961ab@haskell.org> References: <044.5e703c77c226248ade6b1c9ac24961ab@haskell.org> Message-ID: <059.6a348ffd996ade330ed45bfa20015091@haskell.org> #12498: Support unconventionally named import libraries -------------------------------------+------------------------------------- Reporter: Phyx- | Owner: Phyx- Type: feature request | Status: new Priority: normal | Milestone: 8.4.1 Component: Runtime System | Version: 8.0.1 (Linker) | Resolution: | Keywords: Operating System: Windows | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #11072 | Differential Rev(s): Phab:D3513 Wiki Page: | -------------------------------------+------------------------------------- Changes (by Phyx-): * owner: (none) => Phyx- -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jun 3 00:34:22 2017 From: ghc-devs at haskell.org (GHC) Date: Sat, 03 Jun 2017 00:34:22 -0000 Subject: [GHC] #13757: Are you for or against writing "otherwise" as a keyword? In-Reply-To: <044.a4fc99e00f379531d171337bd3da9d21@haskell.org> References: <044.a4fc99e00f379531d171337bd3da9d21@haskell.org> Message-ID: <059.c789222a5d70c6cea0d4e6639a8b5709@haskell.org> #13757: Are you for or against writing "otherwise" as a keyword? -------------------------------------+------------------------------------- Reporter: vanto | Owner: (none) Type: feature request | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 8.0.2 Resolution: wontfix | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Poor/confusing | Unknown/Multiple error message | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by dfeuer): * status: new => closed * resolution: => wontfix Comment: As one of the people tasked by GHC HQ with the job of managing tickets, I am closing this. goldfire's say-so would be sufficient. nomeata's say-so would also be sufficient. I also say this is the wrong process, and I also say that following the right process you are very unlikely to succeed. Please do not reopen this ticket. If you have further questions, you should probably ask in the #haskell channel on FreeNode, or the haskellquestions subreddit. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jun 3 03:27:43 2017 From: ghc-devs at haskell.org (GHC) Date: Sat, 03 Jun 2017 03:27:43 -0000 Subject: [GHC] #13780: Nightmarish pretty-printing of equality type in GHC 8.2 error message In-Reply-To: <050.1bf0abe11448fb7d29d255c23fc5b878@haskell.org> References: <050.1bf0abe11448fb7d29d255c23fc5b878@haskell.org> Message-ID: <065.51cde3cdc1a969733b3db19db4033d19@haskell.org> #13780: Nightmarish pretty-printing of equality type in GHC 8.2 error message -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.2.1-rc2 checker) | Resolution: | Keywords: TypeInType Operating System: Unknown/Multiple | Architecture: Type of failure: Poor/confusing | Unknown/Multiple error message | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * cc: simonpj (added) Comment: This was caused by either commit 77bb09270c70455bbd547470c4e995707d19f37d ( Re-add FunTy (big patch)) or e368f3265b80aeb337fbac3f6a70ee54ab14edfd (Major patch to introduce TyConBinder). I can't know for sure since commit 77bb09270c70455bbd547470c4e995707d19f37d doesn't build properly. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jun 3 05:50:28 2017 From: ghc-devs at haskell.org (GHC) Date: Sat, 03 Jun 2017 05:50:28 -0000 Subject: [GHC] #9630: compile-time performance regression (probably due to Generics) In-Reply-To: <042.a529e5f70870528e7f8796a28ce82a84@haskell.org> References: <042.a529e5f70870528e7f8796a28ce82a84@haskell.org> Message-ID: <057.9f59a8fd80f1336faf209cf59a68e394@haskell.org> #9630: compile-time performance regression (probably due to Generics) -------------------------------------+------------------------------------- Reporter: hvr | Owner: dfeuer Type: bug | Status: new Priority: high | Milestone: 8.2.1 Component: Compiler | Version: 7.9 Resolution: | Keywords: deriving- | perf, Generics Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: #9583, #10293, | Differential Rev(s): #13059, #10818 | Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): I've confirmed this as well. Before that commit, this is the `-ddump-ds` output: {{{ $cnoDuh_axu :: T -> Integer [LclId, Str=DmdType] $cnoDuh_axu = \ (ds_dTM :: T) -> case ds_dTM of _ [Occ=Dead] { T m_avB -> gnoDuh @ (Maybe (Maybe ())) $dGenDuh_axt m_avB } $cduh_axo :: Integer -> T [LclId, Str=DmdType] $cduh_axo = \ (i_avA :: Integer) -> Duh.T (gduh @ (Maybe (Maybe ())) $dGenDuh_axt i_avA) }}} But after that commit: {{{ $cnoDuh_axw :: T -> Integer [LclId, Str=DmdType] $cnoDuh_axw = let { $dGenDuh_aNk :: GenDuh (Maybe ()) [LclId, Str=DmdType] $dGenDuh_aNk = Duh.$fGenDuhMaybe @ () Duh.$fGenDuh() } in let { $dGenDuh_axC :: GenDuh (Maybe (Maybe ())) [LclId, Str=DmdType] $dGenDuh_axC = Duh.$fGenDuhMaybe @ (Maybe ()) $dGenDuh_aNk } in \ (ds_dTV :: T) -> case ds_dTV of _ [Occ=Dead] { T m_avB -> gnoDuh @ (Maybe (Maybe ())) $dGenDuh_axC m_avB } $cduh_axp :: Integer -> T [LclId, Str=DmdType] $cduh_axp = let { $dGenDuh_aNi :: GenDuh (Maybe ()) [LclId, Str=DmdType] $dGenDuh_aNi = Duh.$fGenDuhMaybe @ () Duh.$fGenDuh() } in let { $dGenDuh_axv :: GenDuh (Maybe (Maybe ())) [LclId, Str=DmdType] $dGenDuh_axv = Duh.$fGenDuhMaybe @ (Maybe ()) $dGenDuh_aNi } in \ (i_avA :: Integer) -> Duh.T (gduh @ (Maybe (Maybe ())) $dGenDuh_axv i_avA) }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jun 3 07:20:53 2017 From: ghc-devs at haskell.org (GHC) Date: Sat, 03 Jun 2017 07:20:53 -0000 Subject: [GHC] #13782: Bullish use of Template Haskell's newName causes GHC internal error In-Reply-To: <050.355b0f2ffb6750de858fbc3a1ccc85be@haskell.org> References: <050.355b0f2ffb6750de858fbc3a1ccc85be@haskell.org> Message-ID: <065.d3a82920238c5db0a40c5fda7e229a1e@haskell.org> #13782: Bullish use of Template Haskell's newName causes GHC internal error -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: high | Milestone: 8.2.1 Component: Template Haskell | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by dfeuer): * priority: normal => high * failure: GHC rejects valid program => Compile-time crash or panic * milestone: => 8.2.1 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jun 3 09:41:00 2017 From: ghc-devs at haskell.org (GHC) Date: Sat, 03 Jun 2017 09:41:00 -0000 Subject: [GHC] #13757: Are you for or against writing "otherwise" as a keyword? In-Reply-To: <044.a4fc99e00f379531d171337bd3da9d21@haskell.org> References: <044.a4fc99e00f379531d171337bd3da9d21@haskell.org> Message-ID: <059.e9f3b6324130b51d0dfc61ab373daaa8@haskell.org> #13757: Are you for or against writing "otherwise" as a keyword? -------------------------------------+------------------------------------- Reporter: vanto | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Poor/confusing | Unknown/Multiple error message | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by vanto): * status: closed => new * resolution: wontfix => Comment: == That's enough! You get the wrong ticket.\\ Golfire was mistaken and then nomeata was mistaken too and now dfeuer too are mistaken by closing this ticket that has nothing to do with "new proposal" in TRAC.\\ You had to answer in the ticket {{{#13764.}}} You make a mistake by answering in this ticket.\\ Correct your own fault in this ticket and recognize the fault you made and be respectful too.\\ I open this ticket again that talks about {{{otherwise.}}} Is that clear? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jun 3 11:18:01 2017 From: ghc-devs at haskell.org (GHC) Date: Sat, 03 Jun 2017 11:18:01 -0000 Subject: =?utf-8?b?W0dIQ10gIzEzNzgzOiDmm7TlkIjnkIbnmoRpbnN0YW5jZSBNb25h?= =?utf-8?q?d_=5B=5D?= Message-ID: <044.b1c3ea1077e9da031d0c2420a8407bc8@haskell.org> #13783: 更合理的instance Monad [] -------------------------------------+------------------------------------- Reporter: zaoqi | Owner: (none) Type: feature | Status: new request | Priority: normal | Milestone: Component: Core | Version: 8.0.1 Libraries | Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: Incorrect result Unknown/Multiple | at runtime Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- 使 {{{#!hs join $ map (\y->map (\x->(x,y)) [1..]) [1..] }}} 的结果更合理: https://github.com/zaoqi/zaoqilc/blob/master/featuring/MonadList.hs -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jun 3 12:28:31 2017 From: ghc-devs at haskell.org (GHC) Date: Sat, 03 Jun 2017 12:28:31 -0000 Subject: [GHC] #13757: Are you for or against writing "otherwise" as a keyword? In-Reply-To: <044.a4fc99e00f379531d171337bd3da9d21@haskell.org> References: <044.a4fc99e00f379531d171337bd3da9d21@haskell.org> Message-ID: <059.72b88dd617310b828993d8d7330ca61e@haskell.org> #13757: Are you for or against writing "otherwise" as a keyword? -------------------------------------+------------------------------------- Reporter: vanto | Owner: (none) Type: feature request | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 8.0.2 Resolution: wontfix | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Poor/confusing | Unknown/Multiple error message | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by Phyx-): * status: new => closed * resolution: => wontfix Comment: Vanto I think you don't understand why the ticket is being closes. You are making a language change proposal in the wrong place. This trac is for compiler bugs and features. Not language changes. This is a GHC specific bug tracker. Language changes affect more than just GHC, there are other Haskell compilers. This amongst others is why we have the different proposal process on github which is not associated with GHC but the Haskell group. Please make your proposal there. Do not keep re-opening the ticket as that serves no point. It will just be closed, ignored or deleted for the reasons I stated above. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jun 3 13:04:10 2017 From: ghc-devs at haskell.org (GHC) Date: Sat, 03 Jun 2017 13:04:10 -0000 Subject: =?utf-8?b?UmU6IFtHSENdICMxMzc4Mzog5pu05ZCI55CG55qEaW5zdGFuY2Ug?= =?utf-8?q?Monad_=5B=5D?= In-Reply-To: <044.b1c3ea1077e9da031d0c2420a8407bc8@haskell.org> References: <044.b1c3ea1077e9da031d0c2420a8407bc8@haskell.org> Message-ID: <059.5eea00d5f832f676d0bbba770207bfb0@haskell.org> #13783: 更合理的instance Monad [] -------------------------------------+------------------------------------- Reporter: zaoqi | Owner: (none) Type: feature request | Status: closed Priority: normal | Milestone: Component: Core Libraries | Version: 8.0.1 Resolution: wontfix | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by ezyang): * status: new => closed * resolution: => wontfix Comment: In English, the reporter is suggesting that the Monad instance of list be rewritten so that it generates a fairer distribution of tuples (in the example above, all tuples generated are of the form `(x, 1)`). The fairness of these types of nondeterminism monads is indeed something that has been investigated in the past (e.g., http://okmij.org/ftp/Computation/LogicT.pdf). Unfortunately, the semantics of the List monad as defined in Haskell are fairly set in stone at this point, and can't be changed without massively breaking existing code. The best course of action is probably to define your own monad with the necessary fairness (do consider using CPS; it's a lot more efficient!) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jun 3 14:04:13 2017 From: ghc-devs at haskell.org (GHC) Date: Sat, 03 Jun 2017 14:04:13 -0000 Subject: [GHC] #13757: Are you for or against writing "otherwise" as a keyword? In-Reply-To: <044.a4fc99e00f379531d171337bd3da9d21@haskell.org> References: <044.a4fc99e00f379531d171337bd3da9d21@haskell.org> Message-ID: <059.e099725b6b126129a7f126133f1c51ef@haskell.org> #13757: Are you for or against writing "otherwise" as a keyword? -------------------------------------+------------------------------------- Reporter: vanto | Owner: (none) Type: feature request | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 8.0.2 Resolution: wontfix | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Poor/confusing | Unknown/Multiple error message | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by vanto): replying to [[span(style=color: #FF0000, Phyx- )]]\\ Hello Phyx- Thank you for your clear answer. I understood what you said. The ticket will remain closed. I have other tickets to close in this case. I'll close them too. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jun 3 14:10:59 2017 From: ghc-devs at haskell.org (GHC) Date: Sat, 03 Jun 2017 14:10:59 -0000 Subject: [GHC] #13764: Creating a ticket named "New proposal" in GHC Trac. In-Reply-To: <044.fd2283d580e269372d43530d3844cede@haskell.org> References: <044.fd2283d580e269372d43530d3844cede@haskell.org> Message-ID: <059.ae9cc1bbda2806bd96633326b74038eb@haskell.org> #13764: Creating a ticket named "New proposal" in GHC Trac. -------------------------------------+------------------------------------- Reporter: vanto | Owner: hvr Type: feature request | Status: closed Priority: normal | Milestone: Component: Trac & Git | Version: 8.0.2 Resolution: invalid | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by vanto): * status: new => closed * resolution: => invalid Comment: This ticket is similar to ticket {{{#13757}}}. That's why I close it -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jun 3 14:13:05 2017 From: ghc-devs at haskell.org (GHC) Date: Sat, 03 Jun 2017 14:13:05 -0000 Subject: [GHC] #13669: Identifier "Otherwise" in guarded equation can crash a program In-Reply-To: <044.2ae7b65cc5d8e7fbba5549a7d3cc3853@haskell.org> References: <044.2ae7b65cc5d8e7fbba5549a7d3cc3853@haskell.org> Message-ID: <059.f753f051497840b73ddc73e16ea34185@haskell.org> #13669: Identifier "Otherwise" in guarded equation can crash a program -------------------------------------+------------------------------------- Reporter: vanto | Owner: (none) Type: feature request | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 8.0.2 Resolution: invalid | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Other | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by vanto): * status: new => closed * resolution: => invalid Comment: This ticket is similar to ticket {{{#13757}}}. That's why I close it -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jun 3 16:05:18 2017 From: ghc-devs at haskell.org (GHC) Date: Sat, 03 Jun 2017 16:05:18 -0000 Subject: [GHC] #13782: Bullish use of Template Haskell's newName causes GHC internal error In-Reply-To: <050.355b0f2ffb6750de858fbc3a1ccc85be@haskell.org> References: <050.355b0f2ffb6750de858fbc3a1ccc85be@haskell.org> Message-ID: <065.e05338db1098d4518507ffd45c6af01e@haskell.org> #13782: Bullish use of Template Haskell's newName causes GHC internal error -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: high | Milestone: 8.2.1 Component: Template Haskell | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: #12503 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * related: => #12503 Comment: As I thought, #12503 is very closely related to this ticket. Both this ticket and #12503 were caused by commit 6746549772c5cc0ac66c0fce562f297f4d4b80a2 (Add kind equalities to GHC). While this ticket concerns using a reified type variable in a function declaration, #12503 was about using a reified kind variable in an instance declaration. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jun 3 17:54:52 2017 From: ghc-devs at haskell.org (GHC) Date: Sat, 03 Jun 2017 17:54:52 -0000 Subject: [GHC] #13751: Runtime crash with <> after concurrent stressing of STM computations In-Reply-To: <046.2e620bb56fd39fe88732c85fa515dde8@haskell.org> References: <046.2e620bb56fd39fe88732c85fa515dde8@haskell.org> Message-ID: <061.4b01ba06c29d5f44931cc7df1f21e4b8@haskell.org> #13751: Runtime crash with <> after concurrent stressing of STM computations -------------------------------------+------------------------------------- Reporter: literon | Owner: simonmar Type: bug | Status: new Priority: highest | Milestone: 8.2.1 Component: Runtime System | Version: 8.0.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Runtime crash | Test Case: Blocked By: | Blocking: Related Tickets: 10414 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonmar): * owner: (none) => simonmar Comment: Yep, I think I've found the cause of this. Working on a fix. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jun 3 18:28:20 2017 From: ghc-devs at haskell.org (GHC) Date: Sat, 03 Jun 2017 18:28:20 -0000 Subject: [GHC] #13757: Are you for or against writing "otherwise" as a keyword? In-Reply-To: <044.a4fc99e00f379531d171337bd3da9d21@haskell.org> References: <044.a4fc99e00f379531d171337bd3da9d21@haskell.org> Message-ID: <059.1788a90041dec0fde2972134e38dd9c5@haskell.org> #13757: Are you for or against writing "otherwise" as a keyword? -------------------------------------+------------------------------------- Reporter: vanto | Owner: (none) Type: feature request | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 8.0.2 Resolution: wontfix | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Poor/confusing | Unknown/Multiple error message | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): Thanks vanto! -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jun 3 18:58:48 2017 From: ghc-devs at haskell.org (GHC) Date: Sat, 03 Jun 2017 18:58:48 -0000 Subject: [GHC] #13606: GHCi segfaults on Windows with D3D code In-Reply-To: <050.af5542bb296b21a9acc9021e3f18425a@haskell.org> References: <050.af5542bb296b21a9acc9021e3f18425a@haskell.org> Message-ID: <065.e5b6432a85b984a6448aedeb1a66ee1e@haskell.org> #13606: GHCi segfaults on Windows with D3D code ----------------------------------+---------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.4.1 Component: GHCi | Version: 8.2.1-rc2 Resolution: fixed | Keywords: Operating System: Windows | Architecture: Unknown/Multiple Type of failure: GHCi crash | Test Case: Blocked By: | Blocking: Related Tickets: #12499 #12498 | Differential Rev(s): Phab:D3513 Wiki Page: | ----------------------------------+---------------------------------------- Changes (by RyanGlScott): * status: new => closed * resolution: => fixed Comment: It does fix this particular test case, yes. My original motivation was to run the `d3d11binding` examples in GHCi, but unfortunately, that still isn't possible after this patch: {{{ $ C:\Users\RyanGlScott\Software\ghc\inplace\bin\runghc .\examples\Triangle.hs ghc-stage2.exe: Could not load `d3dxof.dll'. Reason: addDLL: d3dxof.dll or dependencies not loaded. (Win32 error 126) Triangle.hs: loadArchive "C:\\Users\\RyanGlScott\\Software\\ghc\\inplace\\mingw\\x86_64-w64-mingw32\\lib\\libd3dxof.a": failed }}} However, I believe this is due to a different issue, so I'll close this ticket and open a separate one. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jun 3 19:00:51 2017 From: ghc-devs at haskell.org (GHC) Date: Sat, 03 Jun 2017 19:00:51 -0000 Subject: =?utf-8?b?UmU6IFtHSENdICMxMjEwMjog4oCcQ29uc3RyYWludHMgaW4ga2lu?= =?utf-8?q?ds=E2=80=9D_illegal_family_application_in_instance_=28?= =?utf-8?q?+_documentation_issues=3F=29?= In-Reply-To: <051.c1413ffcad4dfaf42160b6c05930b934@haskell.org> References: <051.c1413ffcad4dfaf42160b6c05930b934@haskell.org> Message-ID: <066.f165ee28e070c9f631cef47c2e63ffb4@haskell.org> #12102: “Constraints in kinds” illegal family application in instance (+ documentation issues?) -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: TypeInType Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #13780 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * related: => #13780 Comment: BTW, I've opened #13780 to track the pretty-printing issue observed in comment:1. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jun 3 21:20:41 2017 From: ghc-devs at haskell.org (GHC) Date: Sat, 03 Jun 2017 21:20:41 -0000 Subject: [GHC] #13784: Infinite loop in compiler without undecidableXXX Message-ID: <048.4697e945d90bb9cb27670fb76dfeebc7@haskell.org> #13784: Infinite loop in compiler without undecidableXXX -------------------------------------+------------------------------------- Reporter: tysonzero | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.2 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- The following code causes the compiler to loop. {{{#!hs {-# LANGUAGE DataKinds, FlexibleContexts, FlexibleInstances, GADTs #-} {-# LANGUAGE KindSignatures, MultiParamTypeClasses, TypeFamilies, TypeOperators #-} module Arithmetic where import Data.Monoid ((<>)) data Product :: [*] -> * where (:*) :: a -> Product as -> Product (a : as) Unit :: Product '[] infixr 5 :* instance Show (Product '[]) where show Unit = "Unit" instance (Show a, Show (Product as)) => Show (Product (a : as)) where show (a :* as) = show a <> " :* " <> show as class Divideable a as where type Divide a as :: [*] divide :: Product as -> (a, Product (Divide a as)) instance Divideable a (a : as) where -- type Divide a (a : as) = as -- Conflicting type family instances, seems like OVERLAPS isn't a thing for type families. divide (a :* as) = (a, as) instance Divideable b as => Divideable b (a : as) where type Divide b (a : as) = a : Divide b as divide (a :* as) = a :* divide as }}} Looks like it is because it is erroneously trying to solve `as ~ Product (Divide a as)` in order to type check `divide`. This bug has been fixed in more recent versions of GHC. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jun 3 21:33:49 2017 From: ghc-devs at haskell.org (GHC) Date: Sat, 03 Jun 2017 21:33:49 -0000 Subject: [GHC] #13606: GHCi segfaults on Windows with D3D code In-Reply-To: <050.af5542bb296b21a9acc9021e3f18425a@haskell.org> References: <050.af5542bb296b21a9acc9021e3f18425a@haskell.org> Message-ID: <065.7dc0858d52cff1ecfe14ffc7075d7bf5@haskell.org> #13606: GHCi segfaults on Windows with D3D code ----------------------------------+---------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.4.1 Component: GHCi | Version: 8.2.1-rc2 Resolution: fixed | Keywords: Operating System: Windows | Architecture: Unknown/Multiple Type of failure: GHCi crash | Test Case: Blocked By: | Blocking: Related Tickets: #12499 #12498 | Differential Rev(s): Phab:D3513 Wiki Page: | ----------------------------------+---------------------------------------- Comment (by RyanGlScott): Never mind, please ignore the "different issue" noise. That error was due to `d3d11binding` improperly specifying an `extra-library` dependency (`d3dxof`). After removing `d3dxof`, all of the `d3d11binding` examples now work without a hitch in GHCi. Thanks, Phyx-! -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jun 3 23:06:55 2017 From: ghc-devs at haskell.org (GHC) Date: Sat, 03 Jun 2017 23:06:55 -0000 Subject: [GHC] #13785: Cannot pacify -Wmonomorphism-restriction with nested pattern bindings Message-ID: <050.18d159eb7cdb8c42329cc34900956e4e@haskell.org> #13785: Cannot pacify -Wmonomorphism-restriction with nested pattern bindings -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 (Type checker) | Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: Poor/confusing Unknown/Multiple | error message Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- I originally observed this issue in the `parsers` library. Here's a minimal example: {{{#!hs {-# LANGUAGE ScopedTypeVariables #-} {-# OPTIONS_GHC -Wmonomorphism-restriction #-} module Bug where class Monad m => C m where c :: (m Char, m Char) foo :: forall m. C m => m Char foo = bar >> baz where (bar, baz) = c }}} If you compile this with a GHC that supports `-Wmonomorphism-restriction` (GHC 8.0.1 or later), it'll rightfully give this warning: {{{ [1 of 1] Compiling Bug ( Bug.hs, interpreted ) Bug.hs:11:5: warning: [-Wmonomorphism-restriction] • The Monomorphism Restriction applies to the bindings for ‘bar’, ‘baz’ Consider giving a type signature for these binders • In an equation for ‘foo’: foo = bar >> baz where (bar, baz) = c | 11 | (bar, baz) = c | ^^^^^^^^^^^^^^ }}} Naturally, I tried to squelch this warning by adding type signatures for `bar` and `baz`: {{{#!hs foo :: forall m. C m => m Char foo = bar >> baz where bar, baz :: m Char (bar, baz) = c }}} But GHC //still// warns! {{{ [1 of 1] Compiling Bug ( Bug.hs, interpreted ) Bug.hs:12:5: warning: [-Wmonomorphism-restriction] • The Monomorphism Restriction applies to the bindings for ‘bar’, ‘baz’ Consider giving a type signature for these binders • In an equation for ‘foo’: foo = bar >> baz where bar, baz :: m Char (bar, baz) = c | 12 | (bar, baz) = c | ^^^^^^^^^^^^^^ }}} And to make things even more absurd, GHC points out a chunk of code which //has// type signatures :) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Jun 4 00:31:34 2017 From: ghc-devs at haskell.org (GHC) Date: Sun, 04 Jun 2017 00:31:34 -0000 Subject: [GHC] #13784: Infinite loop in compiler without undecidableXXX In-Reply-To: <048.4697e945d90bb9cb27670fb76dfeebc7@haskell.org> References: <048.4697e945d90bb9cb27670fb76dfeebc7@haskell.org> Message-ID: <063.6517ff072ed9d30f619aeee5a5204890@haskell.org> #13784: Infinite loop in compiler without undecidableXXX -------------------------------------+------------------------------------- Reporter: tysonzero | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.2.1 Component: Compiler | Version: 8.0.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by dfeuer): * milestone: => 8.2.1 Comment: Do we have a test case for this yet? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Jun 4 02:06:03 2017 From: ghc-devs at haskell.org (GHC) Date: Sun, 04 Jun 2017 02:06:03 -0000 Subject: [GHC] #13617: Segfault in Windows GHCi involving C code compiled with -O4 In-Reply-To: <050.e6156dbdb2fd87e0bc8e4bf60775489f@haskell.org> References: <050.e6156dbdb2fd87e0bc8e4bf60775489f@haskell.org> Message-ID: <065.141962ee86383a1547dae7ffb8061ae2@haskell.org> #13617: Segfault in Windows GHCi involving C code compiled with -O4 --------------------------------+---------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: GHCi | Version: 8.0.2 Resolution: | Keywords: Operating System: Windows | Architecture: Unknown/Multiple Type of failure: GHCi crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | --------------------------------+---------------------------------------- Comment (by RyanGlScott): As Phyx- pointed out to me, `-O4` is just an alias for `-O3` in `gcc` and `clang`, so the issue is really with `-O3`. I've confirmed that setting `gcc-options: -O3` also triggers this segfault, but not with `gcc-options: -O2`. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Jun 4 04:41:14 2017 From: ghc-devs at haskell.org (GHC) Date: Sun, 04 Jun 2017 04:41:14 -0000 Subject: [GHC] #13784: Infinite loop in compiler without undecidableXXX In-Reply-To: <048.4697e945d90bb9cb27670fb76dfeebc7@haskell.org> References: <048.4697e945d90bb9cb27670fb76dfeebc7@haskell.org> Message-ID: <063.6a07adc23f2df7f1003519e3dee3f425@haskell.org> #13784: Infinite loop in compiler without undecidableXXX -------------------------------------+------------------------------------- Reporter: tysonzero | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.2.1 Component: Compiler | Version: 8.0.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): This was fixed in commit 1eec1f21268af907f59b5d5c071a9a25de7369c7 (Another major constraint-solver refactoring). In particular, this reminds me a lot of #12538, wherein overlapping multi-parameter type classes with type families also resulted in an infinite loop at compile-time. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Jun 4 11:05:32 2017 From: ghc-devs at haskell.org (GHC) Date: Sun, 04 Jun 2017 11:05:32 -0000 Subject: =?utf-8?b?UmU6IFtHSENdICMxMzc4Mzog5pu05ZCI55CG55qEaW5zdGFuY2Ug?= =?utf-8?q?Monad_=5B=5D?= In-Reply-To: <044.b1c3ea1077e9da031d0c2420a8407bc8@haskell.org> References: <044.b1c3ea1077e9da031d0c2420a8407bc8@haskell.org> Message-ID: <059.14c5efdb2f5fc71fce49c8c98b39b24f@haskell.org> #13783: 更合理的instance Monad [] -------------------------------------+------------------------------------- Reporter: zaoqi | Owner: (none) Type: feature request | Status: closed Priority: normal | Milestone: Component: Core Libraries | Version: 8.0.1 Resolution: wontfix | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by zaoqi): Replying to [comment:1 ezyang]: > In English, the reporter is suggesting that the Monad instance of list be rewritten so that it generates a fairer distribution of tuples (in the example above, all tuples generated are of the form `(x, 1)`). The fairness of these types of nondeterminism monads is indeed something that has been investigated in the past (e.g., http://okmij.org/ftp/Computation/LogicT.pdf). Unfortunately, the semantics of the List monad as defined in Haskell are fairly set in stone at this point, and can't be changed without massively breaking existing code. The best course of action is probably to define your own monad with the necessary fairness (do consider using CPS; it's a lot more efficient!) What's CPS? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Jun 4 12:37:31 2017 From: ghc-devs at haskell.org (GHC) Date: Sun, 04 Jun 2017 12:37:31 -0000 Subject: [GHC] #7542: GHC doesn't optimize (strict) composition with id In-Reply-To: <046.3bbc04071c1dd827d32f98edcf90fd64@haskell.org> References: <046.3bbc04071c1dd827d32f98edcf90fd64@haskell.org> Message-ID: <061.83c42420b9d0c9c618e98431295da92d@haskell.org> #7542: GHC doesn't optimize (strict) composition with id -------------------------------------+------------------------------------- Reporter: shachaf | Owner: simonpj Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.6.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by spacekitteh): Does this still occur in GHC 8.2? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Jun 4 13:23:54 2017 From: ghc-devs at haskell.org (GHC) Date: Sun, 04 Jun 2017 13:23:54 -0000 Subject: [GHC] #8272: testing if SpLim=$rbp and Sp=$rsp changed performance at all In-Reply-To: <045.ecd7af4f53d7df1147bf6a068ec1e485@haskell.org> References: <045.ecd7af4f53d7df1147bf6a068ec1e485@haskell.org> Message-ID: <060.aa2b4b8751a7bd9bdb61f5328fd3dbf4@haskell.org> #8272: testing if SpLim=$rbp and Sp=$rsp changed performance at all -------------------------------------+------------------------------------- Reporter: carter | Owner: carter Type: task | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.7 Resolution: | Keywords: | callingConvention Operating System: Unknown/Multiple | Architecture: x86_64 Type of failure: Runtime | (amd64) performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by michalt): @simonmar: When you say "terrible time walking the stack", you mean GC, right? I've did some more googling and also found [1] which describes some of the differences between the Haskell and C stacks (eg, the Haskell one is heap allocated and easy to grow, the C one is per capability, etc.) I agree - all of this makes it sound that if we want call/ret, we do need (1). Also I still don't really see how we could use `%rsp` in LLVM backend without pretty large changes (eg, using its stackmaps/safepoints). I have to admit that I'm also less enthusiastic about the whole idea after looking into it a bit. [1] https://www.reddit.com/r/haskell/comments/1wm9n4/question_about_stacks_in_haskell_and_rust/cf3vfeq/ -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Jun 4 16:33:31 2017 From: ghc-devs at haskell.org (GHC) Date: Sun, 04 Jun 2017 16:33:31 -0000 Subject: =?utf-8?b?UmU6IFtHSENdICMxMzc4Mzog5pu05ZCI55CG55qEaW5zdGFuY2Ug?= =?utf-8?q?Monad_=5B=5D?= In-Reply-To: <044.b1c3ea1077e9da031d0c2420a8407bc8@haskell.org> References: <044.b1c3ea1077e9da031d0c2420a8407bc8@haskell.org> Message-ID: <059.406c6d6319bc3b8957e1efc2a59515fb@haskell.org> #13783: 更合理的instance Monad [] -------------------------------------+------------------------------------- Reporter: zaoqi | Owner: (none) Type: feature request | Status: closed Priority: normal | Milestone: Component: Core Libraries | Version: 8.0.1 Resolution: wontfix | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by dfeuer): zaoqi, you should look at [https://hackage.haskell.org/package/logict LogicT] for an example of the continuation-passing style (CPS) approach. But please note that that approach also has severe efficiency problems in some cases. For a solution that's never very fast but also never terribly slow, read the paper called "Reflection Without Remorse". -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Jun 4 17:37:31 2017 From: ghc-devs at haskell.org (GHC) Date: Sun, 04 Jun 2017 17:37:31 -0000 Subject: [GHC] #13786: GHC panic on Mac OS X with "cabal repl" / "stack repl" on GHC 8.0.2 and 7.8.3 Message-ID: <047.0a99d83942bb8bb77d0420502e27819e@haskell.org> #13786: GHC panic on Mac OS X with "cabal repl" / "stack repl" on GHC 8.0.2 and 7.8.3 -------------------------------------+------------------------------------- Reporter: ppelleti | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: GHCi | Version: 8.0.2 Keywords: | Operating System: MacOS X Architecture: x86_64 | Type of failure: Compile-time (amd64) | crash or panic Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- Using [https://github.com/ppelleti/hs-mercury-api this package], I tried doing "stack repl" with GHC 8.0.2: {{{ whiteandnerdy:hs-mercury-api ppelleti$ stack repl The following GHC options are incompatible with GHCi and have not been passed to it: -threaded * * * * * * * * The main module to load is ambiguous. Candidates are: 1. Package `mercury-api' component exe:tmr-firmware with main-is file: /Users/ppelleti/programming/haskell/hs-mercury-api/examples/tmr- firmware.hs 2. Package `mercury-api' component exe:tmr-gpio with main-is file: /Users/ppelleti/programming/haskell/hs-mercury-api/examples/tmr-gpio.hs 3. Package `mercury-api' component exe:tmr-lock with main-is file: /Users/ppelleti/programming/haskell/hs-mercury-api/examples/tmr-lock.hs 4. Package `mercury-api' component exe:tmr-params with main-is file: /Users/ppelleti/programming/haskell/hs-mercury-api/examples/tmr-params.hs 5. Package `mercury-api' component exe:tmr-read with main-is file: /Users/ppelleti/programming/haskell/hs-mercury-api/examples/tmr-read.hs 6. Package `mercury-api' component exe:tmr-write with main-is file: /Users/ppelleti/programming/haskell/hs-mercury-api/examples/tmr-write.hs You can specify which one to pick by: * Specifying targets to stack ghci e.g. stack ghci mercury-api:exe:tmr- firmware * Specifying what the main is e.g. stack ghci --main-is mercury-api:exe :tmr-firmware * Choosing from the candidate above [1..6] * * * * * * * * Specify main module to use (press enter to load none): 4 Loading main module from cadidate 4, --main-is /Users/ppelleti/programming/haskell/hs-mercury-api/examples/tmr-params.hs Configuring GHCi with the following packages: mercury-api GHCi, version 8.0.2: http://www.haskell.org/ghc/ :? for help ghc: panic! (the 'impossible' happened) (GHC version 8.0.2 for x86_64-apple-darwin): Loading temp shared object failed: dlopen(/var/folders/d1/v9ptqpx12mdcxj77509440rc0000gn/T/ghc91859_0/libghc_5.dylib, 5): Symbol not found: _TMR_SR_cmdStopReading Referenced from: /var/folders/d1/v9ptqpx12mdcxj77509440rc0000gn/T/ghc91859_0/libghc_5.dylib Expected in: flat namespace in /var/folders/d1/v9ptqpx12mdcxj77509440rc0000gn/T/ghc91859_0/libghc_5.dylib Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug }}} This bug appears to have been around a while, because it also happens with GHC 7.8.3: {{{ whiteandnerdy:hs-mercury-api ppelleti$ cabal repl Preprocessing library mercury-api-0.1.0.0... GHCi, version 7.8.3: http://www.haskell.org/ghc/ :? for help Loading package ghc-prim ... linking ... done. Loading package integer-gmp ... linking ... done. Loading package base ... linking ... done. Loading package array-0.5.0.0 ... linking ... done. Loading package deepseq-1.3.0.2 ... linking ... done. Loading package bytestring-0.10.4.0 ... linking ... done. Loading package containers-0.5.5.1 ... linking ... done. Loading package binary-0.7.1.0 ... linking ... done. Loading package text-1.2.2.1 ... linking ... done. Loading package hashable-1.2.6.0 ... linking ... done. Loading package unordered-containers-0.2.8.0 ... linking ... done. Loading package clock-0.7.2 ... linking ... done. Loading package old-locale-1.0.0.6 ... linking ... done. Loading package time-1.4.2 ... linking ... done. Loading package unix-2.7.0.1 ... linking ... done. Loading package ansi-terminal-0.6.2.3 ... linking ... done. Loading object (static) dist/build/cbits/api/tmr_strerror.o ... done Loading object (static) dist/build/cbits/api/tmr_param.o ... done Loading object (static) dist/build/cbits/api/hex_bytes.o ... done Loading object (static) dist/build/cbits/api/tm_reader.o ... ghc: panic! (the 'impossible' happened) (GHC version 7.8.3 for x86_64-apple-darwin): Loading temp shared object failed: dlopen(/var/folders/d1/v9ptqpx12mdcxj77509440rc0000gn/T/ghc91576_0/ghc91576_4.dylib, 9): Symbol not found: _TMR_SR_SerialTransportNativeInit Referenced from: /var/folders/d1/v9ptqpx12mdcxj77509440rc0000gn/T/ghc91576_0/ghc91576_4.dylib Expected in: flat namespace in /var/folders/d1/v9ptqpx12mdcxj77509440rc0000gn/T/ghc91576_0/ghc91576_4.dylib Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug }}} I'm using Mac OS X 10.9.5: {{{ whiteandnerdy:hs-mercury-api ppelleti$ uname -a Darwin whiteandnerdy.lan 13.4.0 Darwin Kernel Version 13.4.0: Mon Jan 11 18:17:34 PST 2016; root:xnu-2422.115.15~1/RELEASE_X86_64 x86_64 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Jun 4 19:59:57 2017 From: ghc-devs at haskell.org (GHC) Date: Sun, 04 Jun 2017 19:59:57 -0000 Subject: [GHC] #13786: GHC panic on Mac OS X with "cabal repl" / "stack repl" on GHC 8.0.2 and 7.8.3 In-Reply-To: <047.0a99d83942bb8bb77d0420502e27819e@haskell.org> References: <047.0a99d83942bb8bb77d0420502e27819e@haskell.org> Message-ID: <062.d97cbb1d5f72f06c2504a2d8d2f6ea4f@haskell.org> #13786: GHC panic on Mac OS X with "cabal repl" / "stack repl" on GHC 8.0.2 and 7.8.3 -------------------------------------+------------------------------------- Reporter: ppelleti | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: GHCi | Version: 8.0.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * os: MacOS X => Unknown/Multiple * architecture: x86_64 (amd64) => Unknown/Multiple Comment: This is also reproducible on Linux: {{{ $ cabal repl Preprocessing library mercury-api-0.1.0.0... GHCi, version 8.0.2: http://www.haskell.org/ghc/ :? for help ghc: panic! (the 'impossible' happened) (GHC version 8.0.2 for x86_64-unknown-linux): Loading temp shared object failed: /tmp/ghc25635_0/libghc_7.so: undefined symbol: TMR_SR_SerialTransportNativeInit Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Jun 4 20:00:34 2017 From: ghc-devs at haskell.org (GHC) Date: Sun, 04 Jun 2017 20:00:34 -0000 Subject: [GHC] #13786: GHC panic with "cabal repl" / "stack repl" on GHC 8.0.2 and 7.8.3 (was: GHC panic on Mac OS X with "cabal repl" / "stack repl" on GHC 8.0.2 and 7.8.3) In-Reply-To: <047.0a99d83942bb8bb77d0420502e27819e@haskell.org> References: <047.0a99d83942bb8bb77d0420502e27819e@haskell.org> Message-ID: <062.bed0e37d539cbec1f5d3316f796b6336@haskell.org> #13786: GHC panic with "cabal repl" / "stack repl" on GHC 8.0.2 and 7.8.3 -------------------------------------+------------------------------------- Reporter: ppelleti | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: GHCi | Version: 8.0.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Jun 4 22:11:50 2017 From: ghc-devs at haskell.org (GHC) Date: Sun, 04 Jun 2017 22:11:50 -0000 Subject: [GHC] #13787: The compiler told me to report this. I have no idea what happened Message-ID: <050.aae75ada21fe5a7945a3fbcc782dc887@haskell.org> #13787: The compiler told me to report this. I have no idea what happened -------------------------------------+------------------------------------- Reporter: gleb_dianov | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Keywords: | Operating System: Linux Architecture: x86_64 | Type of failure: Compile-time (amd64) | crash or panic Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- Hi, Here is the error: ghc: panic! (the 'impossible' happened) (GHC version 8.0.2 for x86_64-unknown-linux): initTc: unsolved constraints WC {wc_insol = [W] err_aaeS :: t_aaeR[tau:1] (CHoleCan: err)} {{{#!hs teach :: l ~ S l' => ErrorFunction m -> ErrorFunction o -> LearningRate -> Vector (Example i o) m -> Network i l o -> Either StopCriteria (Either Error Iterations) -> NetowrkArgs i l o -> NetworkArgs i l o teach totalErr errF learnRate examples stopCriteria network args = teachNetwork network 0 where teachNetwork :: Network i l o -> Iterations -> Network i l o teachNetwork net i | not $ shouldStop stopCriteria (networkError net) i = teachNetwork (foldl updateNetworkHelper net examples) (i + 1) | otherwise = net networkError :: Network i l o -> Error networkError = undefined updateNetworkHelper :: Network i l o -> Example i o -> Network i l o updateNetworkHelper net@(layer :~~ netTail) example = if example ^. output == runNetwork net (examples ^. input) then net else snd $ updateNetwork layer netTail errF (example ^. inputs) (example ^. outputs) }}} This function broke the compiler. Here is a link to the git repo with this code (module Network) https://gitlab.com/gleb_dianov/neural-haskell With this project I wanted to show how cool Haskell is, but now I can only show how GHC crashes :( -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Jun 4 22:19:31 2017 From: ghc-devs at haskell.org (GHC) Date: Sun, 04 Jun 2017 22:19:31 -0000 Subject: [GHC] #13787: The compiler told me to report this. I have no idea what happened In-Reply-To: <050.aae75ada21fe5a7945a3fbcc782dc887@haskell.org> References: <050.aae75ada21fe5a7945a3fbcc782dc887@haskell.org> Message-ID: <065.9cf538f4a6d76f57e7abd62af7b46897@haskell.org> #13787: The compiler told me to report this. I have no idea what happened -------------------------------------+------------------------------------- Reporter: gleb_dianov | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.2 Resolution: | Keywords: Operating System: Linux | Architecture: x86_64 Type of failure: Compile-time | (amd64) crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by gleb_dianov): * version: 8.0.1 => 8.0.2 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Jun 4 22:29:43 2017 From: ghc-devs at haskell.org (GHC) Date: Sun, 04 Jun 2017 22:29:43 -0000 Subject: [GHC] #12056: Too aggressive `-w` option In-Reply-To: <042.615977cbd760a0223c1133d5e2a0fac1@haskell.org> References: <042.615977cbd760a0223c1133d5e2a0fac1@haskell.org> Message-ID: <057.55f3566ce9f90158e45dbea260d9c4a6@haskell.org> #12056: Too aggressive `-w` option -------------------------------------+------------------------------------- Reporter: asr | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: #11429, #11789 | Differential Rev(s): Phab:D3581 Wiki Page: | -------------------------------------+------------------------------------- Changes (by sgillespie): * differential: => Phab:D3581 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Jun 4 22:32:48 2017 From: ghc-devs at haskell.org (GHC) Date: Sun, 04 Jun 2017 22:32:48 -0000 Subject: [GHC] #12056: Too aggressive `-w` option In-Reply-To: <042.615977cbd760a0223c1133d5e2a0fac1@haskell.org> References: <042.615977cbd760a0223c1133d5e2a0fac1@haskell.org> Message-ID: <057.0448cb44808fc5a986b03414b4fc119e@haskell.org> #12056: Too aggressive `-w` option -------------------------------------+------------------------------------- Reporter: asr | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: #11429, #11789 | Differential Rev(s): Phab:D3581 Wiki Page: | -------------------------------------+------------------------------------- Comment (by sgillespie): I added a Phab differential. The changeset does indeed solve the original symptom, but it is probably not polished enough to be accepted. Nevertheless, I would really like to get some feedback, as I had to make changes in several places. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Jun 4 22:34:54 2017 From: ghc-devs at haskell.org (GHC) Date: Sun, 04 Jun 2017 22:34:54 -0000 Subject: [GHC] #13787: The compiler told me to report this. I have no idea what happened In-Reply-To: <050.aae75ada21fe5a7945a3fbcc782dc887@haskell.org> References: <050.aae75ada21fe5a7945a3fbcc782dc887@haskell.org> Message-ID: <065.7512c93a7553d97b32e419403c829f32@haskell.org> #13787: The compiler told me to report this. I have no idea what happened -------------------------------------+------------------------------------- Reporter: gleb_dianov | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.2 Resolution: | Keywords: Operating System: Linux | Architecture: x86_64 Type of failure: Compile-time | (amd64) crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Description changed by gleb_dianov: @@ -37,0 +37,4 @@ + + UPD. + I updated to lts-8.16. Then I commented out the function and compiled the + project and when I uncommented it the compiler didn't crash New description: Hi, Here is the error: ghc: panic! (the 'impossible' happened) (GHC version 8.0.2 for x86_64-unknown-linux): initTc: unsolved constraints WC {wc_insol = [W] err_aaeS :: t_aaeR[tau:1] (CHoleCan: err)} {{{#!hs teach :: l ~ S l' => ErrorFunction m -> ErrorFunction o -> LearningRate -> Vector (Example i o) m -> Network i l o -> Either StopCriteria (Either Error Iterations) -> NetowrkArgs i l o -> NetworkArgs i l o teach totalErr errF learnRate examples stopCriteria network args = teachNetwork network 0 where teachNetwork :: Network i l o -> Iterations -> Network i l o teachNetwork net i | not $ shouldStop stopCriteria (networkError net) i = teachNetwork (foldl updateNetworkHelper net examples) (i + 1) | otherwise = net networkError :: Network i l o -> Error networkError = undefined updateNetworkHelper :: Network i l o -> Example i o -> Network i l o updateNetworkHelper net@(layer :~~ netTail) example = if example ^. output == runNetwork net (examples ^. input) then net else snd $ updateNetwork layer netTail errF (example ^. inputs) (example ^. outputs) }}} This function broke the compiler. Here is a link to the git repo with this code (module Network) https://gitlab.com/gleb_dianov/neural-haskell With this project I wanted to show how cool Haskell is, but now I can only show how GHC crashes :( UPD. I updated to lts-8.16. Then I commented out the function and compiled the project and when I uncommented it the compiler didn't crash -- -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 5 06:37:12 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 05 Jun 2017 06:37:12 -0000 Subject: [GHC] #13761: Can't create poly-kinded GADT with TypeInType enabled, but can without In-Reply-To: <050.2f1e1c074cee1d6dee365ff75365056c@haskell.org> References: <050.2f1e1c074cee1d6dee365ff75365056c@haskell.org> Message-ID: <065.152f2314620217eba29a820008c3c344@haskell.org> #13761: Can't create poly-kinded GADT with TypeInType enabled, but can without -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.1 checker) | Resolution: invalid | Keywords: TypeInType Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): I'm only questioning whether we need new syntax. Let me re-state what I think you are saying. * The kind of a type constructor can be ''inferred'' from its definition, or ''specified'' by a CUSK. * A CUSK ''specifies'' the kind of a type constructor, fully. No need to look at any other definitions etc; it all comes from the CUSK. * In type declarations you can add kind signatures but they merely specify additional constraints that may guide the inference process. For example {{{ data T (a :: k -> *) = ... }}} constraints `a` to have a kind of the specified form, but it does no more than that. The thing you say is "incredibly confusing" is that the switch from inferred to specified is based on some fairly subtle syntactic rules, and you'd like to have a clearer syntactic distinction. It's a software engineering issue, not a technical one. Separate kind signatures would be one solution. Simplifying the CUSK rules might be another. The [https://downloads.haskell.org/~ghc/latest/docs/html/users_guide/glasgow_exts.html #complete-user-supplied-kind-signatures-and-polymorphic-recursion existing rules] are not bad, actually, except for the mysterious second bullet which depends on explicit quantification of kind variables. Otherwise the rule is ''it has a CUSK if every argument variable, and result kind have explicit signatures''. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 5 07:23:41 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 05 Jun 2017 07:23:41 -0000 Subject: [GHC] #9630: compile-time performance regression (probably due to Generics) In-Reply-To: <042.a529e5f70870528e7f8796a28ce82a84@haskell.org> References: <042.a529e5f70870528e7f8796a28ce82a84@haskell.org> Message-ID: <057.26e7f1fc400ea32363a5d8c75663f969@haskell.org> #9630: compile-time performance regression (probably due to Generics) -------------------------------------+------------------------------------- Reporter: hvr | Owner: dfeuer Type: bug | Status: new Priority: high | Milestone: 8.2.1 Component: Compiler | Version: 7.9 Resolution: | Keywords: deriving- | perf, Generics Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: #9583, #10293, | Differential Rev(s): #13059, #10818 | Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): I can see that you get two copies of the same code, which CSE will presumably get rid of. That might be worth trying to fix. But why does it lead to a 26x increase in compilation time? I'd expect it to be un-noticeable. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 5 08:09:31 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 05 Jun 2017 08:09:31 -0000 Subject: [GHC] #13657: Documentation: Functional dependencies by other means In-Reply-To: <043.e6a2276b874588c5228bad3b9ffdb642@haskell.org> References: <043.e6a2276b874588c5228bad3b9ffdb642@haskell.org> Message-ID: <058.f74c0ec81d44bcb85f909b32830b25dc@haskell.org> #13657: Documentation: Functional dependencies by other means -------------------------------------+------------------------------------- Reporter: AntC | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Documentation | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Documentation | Unknown/Multiple bug | Test Case: Blocked By: | Blocking: Related Tickets: 10431 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): > What does GHC HQ see as the 'organising principle' for the collaborative doo-hickeys? To be honest, we don't really have one, yet anyway. It's so dependent on what people write. And I'm the wrong person to suggest organisation, because I know too much about how GHC works. Better if it was someone like you, who is looking at it from a user point of view. So please go ahead and re-organise! Everyone will thank you for it. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 5 08:10:27 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 05 Jun 2017 08:10:27 -0000 Subject: [GHC] #13657: Documentation: Functional dependencies by other means In-Reply-To: <043.e6a2276b874588c5228bad3b9ffdb642@haskell.org> References: <043.e6a2276b874588c5228bad3b9ffdb642@haskell.org> Message-ID: <058.d8b022295df3d66fc7cbfcd66047d858@haskell.org> #13657: Documentation: Functional dependencies by other means -------------------------------------+------------------------------------- Reporter: AntC | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Documentation | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Documentation | Unknown/Multiple bug | Test Case: Blocked By: | Blocking: Related Tickets: 10431 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): > I still think the User Manual doesn't really explain the difference between SuperClass constraints vs Instance constraints. PS: I'm sure you are right. If you had some specific proposed text to offer, I'd gladly review and add it. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 5 08:43:16 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 05 Jun 2017 08:43:16 -0000 Subject: [GHC] #13784: Infinite loop in compiler without undecidableXXX In-Reply-To: <048.4697e945d90bb9cb27670fb76dfeebc7@haskell.org> References: <048.4697e945d90bb9cb27670fb76dfeebc7@haskell.org> Message-ID: <063.32566f452c3baeba23d1166dbfc35a5c@haskell.org> #13784: Infinite loop in compiler without undecidableXXX -------------------------------------+------------------------------------- Reporter: tysonzero | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.2.1 Component: Compiler | Version: 8.0.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Simon Peyton Jones ): In [changeset:"6597f0846904dc5accbe2556badbd29a8a58c28e/ghc" 6597f08/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="6597f0846904dc5accbe2556badbd29a8a58c28e" Test Trac #13784 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 5 08:53:18 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 05 Jun 2017 08:53:18 -0000 Subject: [GHC] #13774: Singletons code fails to typecheck when type signature involving type family is added In-Reply-To: <050.ab332347289424d0148182ea2be617f8@haskell.org> References: <050.ab332347289424d0148182ea2be617f8@haskell.org> Message-ID: <065.42b4c72e52fe664111e4670eed75e918@haskell.org> #13774: Singletons code fails to typecheck when type signature involving type family is added -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.1 checker) | Keywords: FunDeps, Resolution: invalid | TypeFamilies Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * status: new => closed * resolution: => invalid Comment: Your type signature {{{ sT2 :: Sing (L2r 'False) }}} means {{{ sT2 :: forall k. Sing k (L2r Bool k 'False) }}} And, since `k` is universally quantified, we can't unify it with `Nat`. So the instance doesn't match. You can fix it thus {{{ sT2 :: Sing (L2r 'False :: Nat) }}} which indeed compiles fine. I'm not sure what other error message would be better. I'll close as invalid for now. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 5 09:18:17 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 05 Jun 2017 09:18:17 -0000 Subject: [GHC] #13775: Type family expansion is too lazy, allows accepting of ill-typed terms In-Reply-To: <045.09c124a40b32f046227808df7e0aa665@haskell.org> References: <045.09c124a40b32f046227808df7e0aa665@haskell.org> Message-ID: <060.e1950763762b0a43922379040adc46cd@haskell.org> #13775: Type family expansion is too lazy, allows accepting of ill-typed terms -------------------------------------+------------------------------------- Reporter: fizruk | Owner: diatchki Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.2 checker) | Keywords: Resolution: | CustomTypeErrors Operating System: Unknown/Multiple | Architecture: Type of failure: GHC accepts | Unknown/Multiple invalid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * owner: (none) => diatchki Comment: This is really a question for Iavor, who implemented user-specified type errors. The [http://downloads.haskell.org/~ghc/master/users- guide/glasgow_exts.html#custom-compile-time-errors user manual section on custom errors] does not explain the behaviour of the feature (except with a single example), and need some serious love. What is happening is this: * GHC only reports custom type errors if * We have an ''unsolved'' constraint involving `TypeError` * We have a declared or inferred type involving `TypeError` * We get a constraint `Show (Proxy (TypeError "..."))`. * But the instance for `Proxy` is {{{ instance Show (Proxy s) where ... }}} so the `TypeError...` is discarded. * All constraints are solved, so no error is reported. Iavor: you may want to consider being more aggressive? Or at least documenting the expected behaviour better. Thanks! -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 5 09:20:15 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 05 Jun 2017 09:20:15 -0000 Subject: [GHC] #13784: Infinite loop in compiler without undecidableXXX In-Reply-To: <048.4697e945d90bb9cb27670fb76dfeebc7@haskell.org> References: <048.4697e945d90bb9cb27670fb76dfeebc7@haskell.org> Message-ID: <063.bf8a3a7ca81265c6d6c63b38b5cadced@haskell.org> #13784: Infinite loop in compiler without undecidableXXX -------------------------------------+------------------------------------- Reporter: tysonzero | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.2.1 Component: Compiler | Version: 8.0.2 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * status: new => closed * resolution: => fixed -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 5 09:59:07 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 05 Jun 2017 09:59:07 -0000 Subject: [GHC] #13780: Nightmarish pretty-printing of equality type in GHC 8.2 error message In-Reply-To: <050.1bf0abe11448fb7d29d255c23fc5b878@haskell.org> References: <050.1bf0abe11448fb7d29d255c23fc5b878@haskell.org> Message-ID: <065.577e08a165c1c78b0919ebe9bc4d08ce@haskell.org> #13780: Nightmarish pretty-printing of equality type in GHC 8.2 error message -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: goldfire Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.2.1-rc2 checker) | Resolution: | Keywords: TypeInType Operating System: Unknown/Multiple | Architecture: Type of failure: Poor/confusing | Unknown/Multiple error message | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * owner: (none) => goldfire Comment: I think this is another piece of fallout from the horrible `uo_thing` mess. We are printing a `Type` in a place where we should printing a `HsType`. Richard is planning it investigate and simplify. c.f. #13601, and [wiki:RichardAndSimon] -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 5 10:31:49 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 05 Jun 2017 10:31:49 -0000 Subject: [GHC] #13770: HEAD: Type mentioned in error won't show up in pattern signature In-Reply-To: <048.bec77fc784cc04e5720ed5fc2293fddf@haskell.org> References: <048.bec77fc784cc04e5720ed5fc2293fddf@haskell.org> Message-ID: <063.3d4fdd323a2f3bd1bf235953ff7dbefb@haskell.org> #13770: HEAD: Type mentioned in error won't show up in pattern signature -------------------------------------+------------------------------------- Reporter: heisenbug | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): Yes, this is a tidying problem. The `PatSkol` constructor does not carry a tidy-able type. It should be treated more like `SigSkol`. But what do we ''want'' the error message to say? Consider {{{ data T a where MkT :: a -> b -> T a f :: T [p] -> Int f (MkT x y) = ... }}} Now, if there is an error in the `...`, involving the skolem `b` bound by the `(MkT x y)` pattern, would we like this? {{{ 'b4' is a rigid type variable bound by a pattern with constructor: MkT :: [p] -> b4 -> T [p] }}} Notice that I have instantiated the universal argument too... I see no alternative to doing so. To be comprehensible we must instantiate the existential argument to match the one reported (remember there may be many nested `MkT` matches). That's what I propose. Sound ok? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 5 10:51:28 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 05 Jun 2017 10:51:28 -0000 Subject: [GHC] #13778: explicitly bidirectional patterns should not report Recursive definition" when used in view pattern expression position In-Reply-To: <048.fda620e420aea7183096bc59fa4898e9@haskell.org> References: <048.fda620e420aea7183096bc59fa4898e9@haskell.org> Message-ID: <063.34d2f8f9df313f5db4a7ab7d8c9e7ac1@haskell.org> #13778: explicitly bidirectional patterns should not report Recursive definition" when used in view pattern expression position -------------------------------------+------------------------------------- Reporter: heisenbug | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.3 Resolution: | Keywords: | PatternSynonyms Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): Harump. I think you want 1. To infer the type of `One` from its "builder" {{{ One = 1 }}} 2. To use that type when inferring the type of the pattern But actually GHC does it the other way round 1. Infer the type of the pattern 2. Use that in checking the type of the "builder" There's a good reason for this. Here's a Note from `RnBinds`: {{{ Note [Pattern synonym builders don't yield dependencies] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ When renaming a pattern synonym that has an explicit builder, references in the builder definition should not be used when calculating dependencies. For example, consider the following pattern synonym definition: pattern P x <- C1 x where P x = f (C1 x) f (P x) = C2 x In this case, 'P' needs to be typechecked in two passes: 1. Typecheck the pattern definition of 'P', which fully determines the type of 'P'. This step doesn't require knowing anything about 'f', since the builder definition is not looked at. 2. Typecheck the builder definition, which needs the typechecked definition of 'f' to be in scope; done by calls oo tcPatSynBuilderBind in TcBinds.tcValBinds. This behaviour is implemented in 'tcValBinds', but it crucially depends on 'P' not being put in a recursive group with 'f' (which would make it look like a recursive pattern synonym a la 'pattern P = P' which is unsound and rejected). }}} So I don't see an easy way to give you want you want. The only think I can think of is to allow some kind of monomorphic recursion. But it's easy to program around, so I'm disinclined to fiddle. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 5 12:14:44 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 05 Jun 2017 12:14:44 -0000 Subject: [GHC] #13788: TypeInType fails to compile old code Message-ID: <042.7ebf871aa776db1d7366b850cb9c8328@haskell.org> #13788: TypeInType fails to compile old code -------------------------------------+------------------------------------- Reporter: br1 | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.1-rc2 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: GHC rejects Unknown/Multiple | valid program Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- {{{ {-# LANGUAGE TypeInType #-} module PP where newtype Field l v = Field { value :: v } label :: Field l v -> l label = undefined class HEq x hEq :: HEq x => x -> Int hEq = undefined class HListGet r where hListGet :: r -> Int instance HEq l => HListGet (Field l v) where hListGet f = hEq (label f) }}} fails with {{{ mini.hs:18:29: error: • Couldn't match type ‘k’ with ‘*’ ‘k’ is a rigid type variable bound by the instance declaration at mini.hs:17:5-33 Expected type: Field * l v Actual type: Field k l v • In the first argument of ‘label’, namely ‘f’ In the first argument of ‘hEq’, namely ‘(label f)’ In the expression: hEq (label f) • Relevant bindings include f :: Field k l v (bound at mini.hs:18:14) hListGet :: Field k l v -> Int (bound at mini.hs:18:5) | 18 | hListGet f = hEq (label f) | }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 5 12:24:17 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 05 Jun 2017 12:24:17 -0000 Subject: [GHC] #13785: Cannot pacify -Wmonomorphism-restriction with nested pattern bindings In-Reply-To: <050.18d159eb7cdb8c42329cc34900956e4e@haskell.org> References: <050.18d159eb7cdb8c42329cc34900956e4e@haskell.org> Message-ID: <065.32eed474fbe031e3d7814be2aea7fd3d@haskell.org> #13785: Cannot pacify -Wmonomorphism-restriction with nested pattern bindings -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.1 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Poor/confusing | Unknown/Multiple error message | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Simon Peyton Jones ): In [changeset:"a65dfea535ddf3ca6aa2380ad38cb60cf5c0f1d8/ghc" a65dfea5/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="a65dfea535ddf3ca6aa2380ad38cb60cf5c0f1d8" Make the MR warning more accurage Trac #13785 showed that we were emitting monomorphism warnings when we shouldn't. The fix turned out to be simple. In fact test T10935 then turned out to be another example of the over-noisy warning so I changed the test slightly. }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 5 12:33:17 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 05 Jun 2017 12:33:17 -0000 Subject: [GHC] #13785: Cannot pacify -Wmonomorphism-restriction with nested pattern bindings In-Reply-To: <050.18d159eb7cdb8c42329cc34900956e4e@haskell.org> References: <050.18d159eb7cdb8c42329cc34900956e4e@haskell.org> Message-ID: <065.d0ee6d1b3b23a7ccbcc24a489858a7b5@haskell.org> #13785: Cannot pacify -Wmonomorphism-restriction with nested pattern bindings -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.1 checker) | Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Poor/confusing | Test Case: error message | typecheck/should_compile/T13785 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * status: new => closed * testcase: => typecheck/should_compile/T13785 * resolution: => fixed Comment: Ah yes, thank you. Fixed. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 5 13:00:03 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 05 Jun 2017 13:00:03 -0000 Subject: [GHC] #9173: Better type error messages In-Reply-To: <046.f8f24aa2ddaa3d579bc40f0b6f04f6b7@haskell.org> References: <046.f8f24aa2ddaa3d579bc40f0b6f04f6b7@haskell.org> Message-ID: <061.53105c94445379519cf7e7b07920c1dd@haskell.org> #9173: Better type error messages -------------------------------------+------------------------------------- Reporter: simonpj | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.8.2 Resolution: | Keywords: | TypeErrorMessages Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by vanto): Replying to [[span(style=color: #FF0000, simonpj )]]\\ Hello simonpj,\\ I agree with rwbarton. But instead of using the word "context" I prefer the use of the word "signature".\\ A signature is a description of each component of a definition of a function, or in a more general way by talking about an expression.\\ A Type signature defined by the programmer takes precedence over the Type of the result of the calculated function.\\ We could write : {{{Type `Int` expected by signature}}}.\\ or this sentence that is simple and sounds well\\ {{{ The Type of the result is not in accordance with the Type of the signature }}} Or with the Type write inside\\ {{{ The Type `[Char]` of the result is not in accordance with the Type `Int` of the signature }}} The word "context" is quite different.\\ It implies a greater scope in the code. It would be the equivalent of a set.\\ But one thing must be noted.\\ This thing is not to write the signature of the function.\\ If I write\\ {{{ module Foo where addThree = \x -> x + 3 y = addThree $ Just 5 }}} GHCi sayd\\ {{{ Prelude> :l foo.hs [1 of 1] Compiling Foo ( foo.hs, interpreted ) foo.hs:2:22: error: * No instance for (Num (Maybe a0)) arising from a use of `+' * In the expression: x + 3 In the expression: \ x -> x + 3 In an equation for `addThree': addThree = \ x -> x + 3 foo.hs:3:25: error: * Ambiguous type variable `a0' arising from the literal `5' prevents the constraint `(Num a0)' from being solved. Relevant bindings include y :: Maybe a0 (bound at foo.hs:3:5) Probable fix: use a type annotation to specify what `a0' should be. These potential instances exist: instance Num Integer -- Defined in `GHC.Num' instance Num Double -- Defined in `GHC.Float' instance Num Float -- Defined in `GHC.Float' ...plus two others (use -fprint-potential-instances to see them all) * In the first argument of `Just', namely `5' In the second argument of `($)', namely `Just 5' In the expression: addThree $ Just 5 Failed, modules loaded: none. Prelude> }}} Here there is no Type signature in the context.\\ The sentence {{{* No instance for (Num (Maybe a0)) arising from a use of `+'}}} is more explicit.\\ I hope this will help. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 5 13:08:47 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 05 Jun 2017 13:08:47 -0000 Subject: [GHC] #13745: Investigate compile-time regressions in regex-tdfa-1.2.2 In-Reply-To: <046.b7de3eed99bc2dfd75756f4f73799d3c@haskell.org> References: <046.b7de3eed99bc2dfd75756f4f73799d3c@haskell.org> Message-ID: <061.afe3e5e50f68885234659db6b9c95fb4@haskell.org> #13745: Investigate compile-time regressions in regex-tdfa-1.2.2 -------------------------------------+------------------------------------- Reporter: bgamari | Owner: (none) Type: task | Status: new Priority: high | Milestone: 8.2.1 Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by michalt): * cc: michalt (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 5 13:45:04 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 05 Jun 2017 13:45:04 -0000 Subject: [GHC] #13761: Can't create poly-kinded GADT with TypeInType enabled, but can without In-Reply-To: <050.2f1e1c074cee1d6dee365ff75365056c@haskell.org> References: <050.2f1e1c074cee1d6dee365ff75365056c@haskell.org> Message-ID: <065.f5832a7c283ae603d20b5abef3ceb52f@haskell.org> #13761: Can't create poly-kinded GADT with TypeInType enabled, but can without -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.1 checker) | Resolution: invalid | Keywords: TypeInType Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by goldfire): Replying to [comment:8 simonpj]: > The thing you say is "incredibly confusing" is that the switch from inferred to specified is based on some fairly subtle syntactic rules, and you'd like to have a clearer syntactic distinction. It's a software engineering issue, not a technical one. Yes, precisely. There's no real technical challenge here. I just want an easy way for the user to say what they mean: inference or specification. The problem with the CUSK rules as they are is that sometimes you've written a CUSK when you don't mean to. For example {{{ data T (a :: Proxy k) where ... }}} According to the rules, this declaration has a CUSK. But suppose I want `k`'s kind to be inferred. The only way to do so is to write {{{ data T :: Proxy k -> Type where ... }}} This form is a CUSK with `-XNoTypeInType` but is ''not'' a CUSK with `-XTypeInType`. The reason for the extra rule with `-XTypeInType` is to support this case, where the user wants inference. (Note that with `-XNoTypeInType`, `k`'s kind will always by `Type`, and so the issue of inference doesn't arise.) This particular problem is worse for closed type families and for classes, where there is no alternate syntax available if the user does not want a CUSK. The intent of my proposal is to make all of this simpler: the user simply says whether they want inference (no kind sig) or specification (kind sig). No fiddly rules. No exceptions. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 5 13:52:05 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 05 Jun 2017 13:52:05 -0000 Subject: [GHC] #13778: explicitly bidirectional patterns should not report Recursive definition" when used in view pattern expression position In-Reply-To: <048.fda620e420aea7183096bc59fa4898e9@haskell.org> References: <048.fda620e420aea7183096bc59fa4898e9@haskell.org> Message-ID: <063.3329fb1b9f5ebbab971e01cc77a60003@haskell.org> #13778: explicitly bidirectional patterns should not report Recursive definition" when used in view pattern expression position -------------------------------------+------------------------------------- Reporter: heisenbug | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.3 Resolution: | Keywords: | PatternSynonyms Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by heisenbug): Replying to [comment:2 simonpj]: Hi Simon, adding a type signature won't make the error go away. IIRC this is not a type inference problem. I cannot try now, am AFK. > Harump. I think you want > > 1. To infer the type of `One` from its "builder" > {{{ > One = 1 > }}} > > 2. To use that type when inferring the type of the pattern > > But actually GHC does it the other way round > > 1. Infer the type of the pattern > 2. Use that in checking the type of the "builder" > > There's a good reason for this. Here's a Note from `RnBinds`: > {{{ > Note [Pattern synonym builders don't yield dependencies] > ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ > When renaming a pattern synonym that has an explicit builder, > references in the builder definition should not be used when > calculating dependencies. For example, consider the following pattern > synonym definition: > > pattern P x <- C1 x where > P x = f (C1 x) > > f (P x) = C2 x > > In this case, 'P' needs to be typechecked in two passes: > > 1. Typecheck the pattern definition of 'P', which fully determines the > type of 'P'. This step doesn't require knowing anything about 'f', > since the builder definition is not looked at. > > 2. Typecheck the builder definition, which needs the typechecked > definition of 'f' to be in scope; done by calls oo tcPatSynBuilderBind > in TcBinds.tcValBinds. > > This behaviour is implemented in 'tcValBinds', but it crucially > depends on 'P' not being put in a recursive group with 'f' (which > would make it look like a recursive pattern synonym a la 'pattern P = > P' which is unsound and rejected). > }}} > So I don't see an easy way to give you want you want. > > The only think I can think of is to allow some kind of monomorphic recursion. But it's easy to program around, so I'm disinclined to fiddle. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 5 14:07:37 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 05 Jun 2017 14:07:37 -0000 Subject: [GHC] #13774: Singletons code fails to typecheck when type signature involving type family is added In-Reply-To: <050.ab332347289424d0148182ea2be617f8@haskell.org> References: <050.ab332347289424d0148182ea2be617f8@haskell.org> Message-ID: <065.877d486a0b151553bf31f463547d44e4@haskell.org> #13774: Singletons code fails to typecheck when type signature involving type family is added -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.1 checker) | Keywords: FunDeps, Resolution: invalid | TypeFamilies Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by goldfire): Well spotted -- thanks. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 5 14:19:31 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 05 Jun 2017 14:19:31 -0000 Subject: [GHC] #13788: TypeInType fails to compile old code In-Reply-To: <042.7ebf871aa776db1d7366b850cb9c8328@haskell.org> References: <042.7ebf871aa776db1d7366b850cb9c8328@haskell.org> Message-ID: <057.4e0b2c9fe19632dfb598e83e3448dc09@haskell.org> #13788: TypeInType fails to compile old code -------------------------------------+------------------------------------- Reporter: br1 | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.1-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by goldfire): This looks like correct behavior to me. With `-XTypeInType`, GHC will generalize kinds, including the kind of `HEq` (now `forall k. k -> Constraint`) and of `Field` (now `forall k. k -> Type -> Type`). However, `label` can't be generalized; it has type `forall (l :: Type) (v :: Type). Field @Type l v -> l`. (I'm using `@` to denote a normally-elided parameter.) Because the instance at the end doesn't constraint the kind of `l`, the type of `f` is `Field @k l v`, where `k` is implicitly bound in the instance declaration. Accordingly, it can't be passed to `label`. The solution: add a kind signature: `instance HEq l => HListGet (Field (l :: Type) v) where ...`. (You will have to import `Type` from `Data.Kind`.) Please close the ticket if you agree with my analysis. Thanks! -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 5 14:26:34 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 05 Jun 2017 14:26:34 -0000 Subject: [GHC] #13788: TypeInType fails to compile old code In-Reply-To: <042.7ebf871aa776db1d7366b850cb9c8328@haskell.org> References: <042.7ebf871aa776db1d7366b850cb9c8328@haskell.org> Message-ID: <057.86a3bec1e39bdee2a1dc1f2517eaad77@haskell.org> #13788: TypeInType fails to compile old code -------------------------------------+------------------------------------- Reporter: br1 | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.1-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by br1): Your solution works. The problem is that adding TypeInType requires adding kind signatures all over. Then TypeInType is not an extension but a breaking change. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 5 14:48:59 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 05 Jun 2017 14:48:59 -0000 Subject: [GHC] #13788: TypeInType fails to compile old code In-Reply-To: <042.7ebf871aa776db1d7366b850cb9c8328@haskell.org> References: <042.7ebf871aa776db1d7366b850cb9c8328@haskell.org> Message-ID: <057.a96306b11647304e1e47ff168201870a@haskell.org> #13788: TypeInType fails to compile old code -------------------------------------+------------------------------------- Reporter: br1 | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.1-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by goldfire): This isn't an issue with `TypeInType`, per se, but with `PolyKinds`, which originally added kind generalization. (You'll find that compiling with just `PolyKinds` causes the same effect as you're observing with `TypeInType`.) Many of the language "extensions" have the potential to break code. For example, `OverloadedStrings` can cause declarations like `x = length "hi"` to fail, because GHC can no longer tell what type `"hi"` should be. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 5 14:53:04 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 05 Jun 2017 14:53:04 -0000 Subject: [GHC] #9630: compile-time performance regression (probably due to Generics) In-Reply-To: <042.a529e5f70870528e7f8796a28ce82a84@haskell.org> References: <042.a529e5f70870528e7f8796a28ce82a84@haskell.org> Message-ID: <057.dcc4948dd204f492f5d0e241340a60df@haskell.org> #9630: compile-time performance regression (probably due to Generics) -------------------------------------+------------------------------------- Reporter: hvr | Owner: dfeuer Type: bug | Status: new Priority: high | Milestone: 8.2.1 Component: Compiler | Version: 7.9 Resolution: | Keywords: deriving- | perf, Generics Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: #9583, #10293, | Differential Rev(s): #13059, #10818 | Wiki Page: | -------------------------------------+------------------------------------- Comment (by dfeuer): Replying to [comment:59 simonpj]: > I can see that you get two copies of the same code, which CSE will presumably get rid of. That might be worth trying to fix. > > But why does it lead to a 26x increase in compilation time? I'd expect it to be un-noticeable. Well, it's not always going to cause serious problems, and I think this ticket touches several underlying issues, but it bet it ''can'' cause serious trouble. Suppose you have a class with ten methods, and use generic defaults. Now you'll end up with ten dictionaries of ten methods each. Depending on how inlining goes, I suspect that could be quite bad. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 5 15:36:54 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 05 Jun 2017 15:36:54 -0000 Subject: [GHC] #12056: Too aggressive `-w` option In-Reply-To: <042.615977cbd760a0223c1133d5e2a0fac1@haskell.org> References: <042.615977cbd760a0223c1133d5e2a0fac1@haskell.org> Message-ID: <057.ce2e969489cff8da65a03d65cadc38ed@haskell.org> #12056: Too aggressive `-w` option -------------------------------------+------------------------------------- Reporter: asr | Owner: (none) Type: bug | Status: patch Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: #11429, #11789 | Differential Rev(s): Phab:D3581 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => patch -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 5 15:57:31 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 05 Jun 2017 15:57:31 -0000 Subject: [GHC] #11785: Kinds should be treated like types in TcSplice In-Reply-To: <047.bfff5ba2980e2ce458e592d1077c3dd1@haskell.org> References: <047.bfff5ba2980e2ce458e592d1077c3dd1@haskell.org> Message-ID: <062.44b4d791241f81b4856b8f456ce5e116@haskell.org> #11785: Kinds should be treated like types in TcSplice -------------------------------------+------------------------------------- Reporter: goldfire | Owner: (none) Type: task | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 8.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): Another place we should unify the treatment of `Type`s and `Kind`s is `DsMeta`. We have both `repLTy` and `repLKind`, but the latter covers far fewer things than the former, which has led to bugs like #13781. Sadly, accomplishing this requires more work than you'd believe, since `repLTy` returns a `TypeQ`, whereas `repLKind` returns a pure `Kind`. In other words, we'd have to go through and purify `repLTy`, as well as every function it calls which is also monadic (see https://phabricator.haskell.org/D3627#103117). -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 5 16:11:36 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 05 Jun 2017 16:11:36 -0000 Subject: [GHC] #13786: GHC panic with "cabal repl" / "stack repl" on GHC 8.0.2 and 7.8.3 In-Reply-To: <047.0a99d83942bb8bb77d0420502e27819e@haskell.org> References: <047.0a99d83942bb8bb77d0420502e27819e@haskell.org> Message-ID: <062.5c41189b6da28107dca1f0ad0a59933d@haskell.org> #13786: GHC panic with "cabal repl" / "stack repl" on GHC 8.0.2 and 7.8.3 -------------------------------------+------------------------------------- Reporter: ppelleti | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: GHCi | Version: 8.0.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): Did this package ever work? It looks to me like the object files aren't being passed to `ghc` in dependency-order, hence the link errors. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 5 16:14:59 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 05 Jun 2017 16:14:59 -0000 Subject: [GHC] #13787: The compiler told me to report this. I have no idea what happened In-Reply-To: <050.aae75ada21fe5a7945a3fbcc782dc887@haskell.org> References: <050.aae75ada21fe5a7945a3fbcc782dc887@haskell.org> Message-ID: <065.658ddf06b64036cc18c344d1ecadf592@haskell.org> #13787: The compiler told me to report this. I have no idea what happened -------------------------------------+------------------------------------- Reporter: gleb_dianov | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 8.0.2 Resolution: duplicate | Keywords: Operating System: Linux | Architecture: x86_64 Type of failure: Compile-time | (amd64) crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: #13106 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * status: new => closed * resolution: => duplicate * related: => #13106 Comment: Thanks for the bug report. I don't have time to dig into the internals of your particular project, but there is a 99.9% chance that this is an occurrence of #13106, a known bug which has been fixed in GHC 8.2.1. The underlying cause is usually that you forgot to import some top-level identifier (in your case, probably `err`). -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 5 16:16:22 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 05 Jun 2017 16:16:22 -0000 Subject: [GHC] #13786: GHC panic with "cabal repl" / "stack repl" on GHC 8.0.2 and 7.8.3 In-Reply-To: <047.0a99d83942bb8bb77d0420502e27819e@haskell.org> References: <047.0a99d83942bb8bb77d0420502e27819e@haskell.org> Message-ID: <062.acef8cd6d8b9cc5bde37abb2f6396fbb@haskell.org> #13786: GHC panic with "cabal repl" / "stack repl" on GHC 8.0.2 and 7.8.3 -------------------------------------+------------------------------------- Reporter: ppelleti | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: GHCi | Version: 8.0.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): For the record, I played around with the GHC command line for a bit and got close to getting it to build with the following link order, {{{ api/tmr_strerror.o api/tmr_param.o api/hex_bytes.o api/serial_transport_posix.o api/serial_reader_l3.o api/serial_reader.o api/tm_reader_async.o api/tm_reader.o api/tmr_utils.o glue/glue.o api/osdep_posix.o }}} Unfortunately this also doesn't quite work since `isSecureAccessEnabled` is defined in `serial_reader` but used in both `serial_reader_l3` and `serial_reader`, whereas the latter appears to have dependencies on `serial_reader_l3`, creating a circular dependency. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 5 16:17:08 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 05 Jun 2017 16:17:08 -0000 Subject: [GHC] #13786: GHC panic with "cabal repl" / "stack repl" on GHC 8.0.2 and 7.8.3 In-Reply-To: <047.0a99d83942bb8bb77d0420502e27819e@haskell.org> References: <047.0a99d83942bb8bb77d0420502e27819e@haskell.org> Message-ID: <062.cd3df1c927eef955938483f0654f2f80@haskell.org> #13786: GHC panic with "cabal repl" / "stack repl" on GHC 8.0.2 and 7.8.3 -------------------------------------+------------------------------------- Reporter: ppelleti | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: GHCi | Version: 8.0.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): Since you seem to know more about what's going on here than I do (and because there are several other tickets of this flavor that I'd like to characterize), can you explain what you mean by "dependency-order"? And why that would make a difference as to whether runtime linking would succeed (but apparently not compilation)? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 5 16:18:43 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 05 Jun 2017 16:18:43 -0000 Subject: [GHC] #13786: GHC panic with "cabal repl" / "stack repl" on GHC 8.0.2 and 7.8.3 In-Reply-To: <047.0a99d83942bb8bb77d0420502e27819e@haskell.org> References: <047.0a99d83942bb8bb77d0420502e27819e@haskell.org> Message-ID: <062.334627df77fb773004634f9d1bedc361@haskell.org> #13786: GHC panic with "cabal repl" / "stack repl" on GHC 8.0.2 and 7.8.3 -------------------------------------+------------------------------------- Reporter: ppelleti | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: GHCi | Version: 8.0.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by ppelleti): The package works fine when compiled (i. e. "cabal build" or "stack build"), but this was my first time trying it with GHCi (i. e. "cabal repl" / "stack repl"). I hadn't known the object files needed to be passed in dependency order. Perhaps the error message could be improved, to indicate it is an error on the user's part, rather than a GHC bug? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 5 16:21:13 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 05 Jun 2017 16:21:13 -0000 Subject: [GHC] #13774: Singletons code fails to typecheck when type signature involving type family is added In-Reply-To: <050.ab332347289424d0148182ea2be617f8@haskell.org> References: <050.ab332347289424d0148182ea2be617f8@haskell.org> Message-ID: <065.ba453d55614b63793e3205c7d2108ec1@haskell.org> #13774: Singletons code fails to typecheck when type signature involving type family is added -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.1 checker) | Keywords: FunDeps, Resolution: invalid | TypeFamilies Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): Urgh. I'd like to feign ignorance and claim that I would have never thought in a million years to put in a kind ascription, but this isn't even the first time that this bug has bit me (#11275). So I should probably know better by now... but thanks for patiently explaining to me again anyways :) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 5 16:25:22 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 05 Jun 2017 16:25:22 -0000 Subject: [GHC] #13778: explicitly bidirectional patterns should not report Recursive definition" when used in view pattern expression position In-Reply-To: <048.fda620e420aea7183096bc59fa4898e9@haskell.org> References: <048.fda620e420aea7183096bc59fa4898e9@haskell.org> Message-ID: <063.e8ae9554c490fa381074317d3bfb6775@haskell.org> #13778: explicitly bidirectional patterns should not report Recursive definition" when used in view pattern expression position -------------------------------------+------------------------------------- Reporter: heisenbug | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.3 Resolution: | Keywords: | PatternSynonyms Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): > adding a type signature won't make the error go away I didn't claim that it would! But you give me an idea. If you wrote a pattern signature: {{{ pattern One :: Num a => a pattern One <- ((==One) -> True) where One = 1 }}} then I think we could soundly suppress the check, without messing up the architecture above. Hmm. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 5 16:49:39 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 05 Jun 2017 16:49:39 -0000 Subject: [GHC] #13786: GHC panic with "cabal repl" / "stack repl" on GHC 8.0.2 and 7.8.3 In-Reply-To: <047.0a99d83942bb8bb77d0420502e27819e@haskell.org> References: <047.0a99d83942bb8bb77d0420502e27819e@haskell.org> Message-ID: <062.609bf238531b1a32c5453999e24de9a1@haskell.org> #13786: GHC panic with "cabal repl" / "stack repl" on GHC 8.0.2 and 7.8.3 -------------------------------------+------------------------------------- Reporter: ppelleti | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: GHCi | Version: 8.0.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by ppelleti): I fixed the circular dependency for isSecureAccessEnabled, and got this order to work: {{{ c-sources: cbits/api/serial_transport_posix.c , cbits/api/osdep_posix.c , cbits/api/tmr_strerror.c , cbits/api/tmr_utils.c , cbits/api/tmr_param.c , cbits/api/hex_bytes.c , cbits/api/serial_reader_l3.c , cbits/api/serial_reader.c , cbits/api/tm_reader_async.c , cbits/api/tm_reader.c , cbits/glue/glue.c }}} However, the unpleasant part is that Cabal seems to always put the conditional c-sources after the unconditional c-sources, even if I put the conditional c-sources first in the Cabal file. So, the only workaround seems to be to list all the sources twice: once for POSIX and once for Windows. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 5 16:55:22 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 05 Jun 2017 16:55:22 -0000 Subject: [GHC] #13786: GHC panic with "cabal repl" / "stack repl" on GHC 8.0.2 and 7.8.3 In-Reply-To: <047.0a99d83942bb8bb77d0420502e27819e@haskell.org> References: <047.0a99d83942bb8bb77d0420502e27819e@haskell.org> Message-ID: <062.45785827f91bd42adc68a10365227e9f@haskell.org> #13786: GHC panic with "cabal repl" / "stack repl" on GHC 8.0.2 and 7.8.3 -------------------------------------+------------------------------------- Reporter: ppelleti | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Runtime System | Version: 8.0.2 (Linker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * cc: angerman, Jaffacake, rwbarton (added) * component: GHCi => Runtime System (Linker) Comment: I actually wasn't quite correct. `ld` requires that **archives** be provided on the command line in topological order; that is if `libA` refers to `libB`, they must be provided in the order of `libB libA` (alternatively you can explicitly flag a group of archives as a recursive group using the `--start-group`/`--end-group` flags). However, it turns out that there is no such requirement of object files: it seems that you can give them in any order and `ld` will link them without any trouble. Unfortunately, this isn't true of GHCi's linker. We sequentially load one object file after another, failing if we encounter any undefined reference. Perhaps what we should instead do is load the objects as a group, first slurping in the symbol tables of each of them, and only afterwards try to resolve references. This will add some complexity, but will ensure that we offer the same ordering guarantees that `ld` currently provides. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 5 17:03:49 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 05 Jun 2017 17:03:49 -0000 Subject: [GHC] #13703: Internal libraries regression in GHC 8.2 (ghc-pkg handling) In-Reply-To: <045.0eb24a47df9920808d8c257fd8ac90fc@haskell.org> References: <045.0eb24a47df9920808d8c257fd8ac90fc@haskell.org> Message-ID: <060.b6748eb84ca6a7bce4096dc261661ab8@haskell.org> #13703: Internal libraries regression in GHC 8.2 (ghc-pkg handling) -------------------------------------+------------------------------------- Reporter: ezyang | Owner: (none) Type: bug | Status: new Priority: highest | Milestone: 8.2.1 Component: ghc-pkg | Version: 8.2.1-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3590 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * priority: high => highest * status: closed => new * resolution: fixed => Comment: Judging from [[https://github.com/haskell/cabal/pull/4529|this Cabal bug]] it sounds like this is still broken. ezyang, do you think you could investigate? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 5 17:03:57 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 05 Jun 2017 17:03:57 -0000 Subject: [GHC] #13703: Internal libraries regression in GHC 8.2 (ghc-pkg handling) In-Reply-To: <045.0eb24a47df9920808d8c257fd8ac90fc@haskell.org> References: <045.0eb24a47df9920808d8c257fd8ac90fc@haskell.org> Message-ID: <060.2dd0bfb2d36d84e0d23dee10db1ed0fa@haskell.org> #13703: Internal libraries regression in GHC 8.2 (ghc-pkg handling) -------------------------------------+------------------------------------- Reporter: ezyang | Owner: ezyang Type: bug | Status: new Priority: highest | Milestone: 8.2.1 Component: ghc-pkg | Version: 8.2.1-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3590 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * owner: (none) => ezyang -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 5 17:06:15 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 05 Jun 2017 17:06:15 -0000 Subject: [GHC] #13786: GHCi linker is dependent upon object file order (was: GHC panic with "cabal repl" / "stack repl" on GHC 8.0.2 and 7.8.3) In-Reply-To: <047.0a99d83942bb8bb77d0420502e27819e@haskell.org> References: <047.0a99d83942bb8bb77d0420502e27819e@haskell.org> Message-ID: <062.a241207f8997dc81ebfafe55a48879a6@haskell.org> #13786: GHCi linker is dependent upon object file order -------------------------------------+------------------------------------- Reporter: ppelleti | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Runtime System | Version: 8.0.2 (Linker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 5 17:06:38 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 05 Jun 2017 17:06:38 -0000 Subject: [GHC] #13788: TypeInType fails to compile old code In-Reply-To: <042.7ebf871aa776db1d7366b850cb9c8328@haskell.org> References: <042.7ebf871aa776db1d7366b850cb9c8328@haskell.org> Message-ID: <057.a1e0ca89d7db294c974a4777351a24b2@haskell.org> #13788: TypeInType fails to compile old code -------------------------------------+------------------------------------- Reporter: br1 | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 8.2.1-rc2 Resolution: invalid | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by br1): * status: new => closed * resolution: => invalid Comment: I see now. Thanks! -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 5 18:18:23 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 05 Jun 2017 18:18:23 -0000 Subject: [GHC] #13775: Type family expansion is too lazy, allows accepting of ill-typed terms In-Reply-To: <045.09c124a40b32f046227808df7e0aa665@haskell.org> References: <045.09c124a40b32f046227808df7e0aa665@haskell.org> Message-ID: <060.3d9e5db9b7613bd339997f035961ca2a@haskell.org> #13775: Type family expansion is too lazy, allows accepting of ill-typed terms -------------------------------------+------------------------------------- Reporter: fizruk | Owner: diatchki Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.2 checker) | Keywords: Resolution: | CustomTypeErrors Operating System: Unknown/Multiple | Architecture: Type of failure: GHC accepts | Unknown/Multiple invalid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by diatchki): I think that this is more a question about how type functions work, rather than `TypeError` specifically. Currently, GHC does not evaluate type functions unless it needs to, so there is no error reported. Similarly, GHC does not report any errors for the following example, which has nothing to do with `TypeError`: {{{ type family F a test = show (Proxy @ (Proxy (F Int)) }}} This works just fine and prints `Proxy`, it does not report a missing instance for `F Int`. I don't really like this behavior of GHC, but that's an orthogonal issue. I am not sure how I could be more aggressive with `TypeError` without a bunch of special cases, and also, last time we discussed this people seemed to want the lazy behavior. I'll take on updating the manual to be more explicit about the behavior. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 5 18:36:52 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 05 Jun 2017 18:36:52 -0000 Subject: [GHC] #13786: GHCi linker is dependent upon object file order In-Reply-To: <047.0a99d83942bb8bb77d0420502e27819e@haskell.org> References: <047.0a99d83942bb8bb77d0420502e27819e@haskell.org> Message-ID: <062.4cd62cfe535ae93811adc0b92cd64233@haskell.org> #13786: GHCi linker is dependent upon object file order -------------------------------------+------------------------------------- Reporter: ppelleti | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Runtime System | Version: 8.0.2 (Linker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Phyx-): The complexity shouldn't be all that much. Just delay the calls to `ocResolve` until all `ocGetNames` is done should be enough. There's no real reason that we have to call the three stages sequentially off the top of my head. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 5 19:09:12 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 05 Jun 2017 19:09:12 -0000 Subject: [GHC] #13787: The compiler told me to report this. I have no idea what happened In-Reply-To: <050.aae75ada21fe5a7945a3fbcc782dc887@haskell.org> References: <050.aae75ada21fe5a7945a3fbcc782dc887@haskell.org> Message-ID: <065.80df45f0e14d4a7722f9aba0fb2b8e46@haskell.org> #13787: The compiler told me to report this. I have no idea what happened -------------------------------------+------------------------------------- Reporter: gleb_dianov | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 8.0.2 Resolution: duplicate | Keywords: Operating System: Linux | Architecture: x86_64 Type of failure: Compile-time | (amd64) crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: #13106 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by gleb_dianov): Replying to [comment:3 RyanGlScott]: > Thanks for the bug report. I don't have time to dig into the internals of your particular project, but there is a 99.9% chance that this is an occurrence of #13106, a known bug which has been fixed in GHC 8.2.1. The underlying cause is usually that you forgot to import some top-level identifier (in your case, probably `err`). This error didn't occur after I fixed some compile-time errors in the module (didn't have any problems with imports though), so I'm happy -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 5 20:09:02 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 05 Jun 2017 20:09:02 -0000 Subject: [GHC] #10600: -fwarn-incomplete-patterns doesn't work with -fno-code In-Reply-To: <043.972d3170891da80a4e96bca7b675a836@haskell.org> References: <043.972d3170891da80a4e96bca7b675a836@haskell.org> Message-ID: <058.85bf49e5b5d49bf258914d6d23ab65b5@haskell.org> #10600: -fwarn-incomplete-patterns doesn't work with -fno-code -------------------------------------+------------------------------------- Reporter: akio | Owner: ezyang Type: bug | Status: new Priority: normal | Milestone: 8.4.1 Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple warning at compile-time | Test Case: driver/T8101b Blocked By: | Blocking: Related Tickets: #8101 | Differential Rev(s): Phab:D1278 Wiki Page: | -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"c9eb4385aad248118650725b7b699bb97ee21c0d/ghc" c9eb4385/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="c9eb4385aad248118650725b7b699bb97ee21c0d" Desugar modules compiled with -fno-code Previously modules with hscTarget == HscNothing were not desugared. This patch changes behavior so that all modules HsSrcFile Modules except GHC.Prim are desugared. Modules with hscTarget == HscNothing are not simplified. Warnings and errors produced by the desugarer will now be produced when compiling with -fno-code. HscMain.finishTypecheckingOnly is removed, HscMain.hscIncrementalCompile is simplified a bit, and HscMain.finish takes in the removed logic. I think this is easier to follow. Updates haddock submodule. Tests T8101, T8101b, T10600 are no longer expect_broken. Reviewers: ezyang, austin, bgamari Subscribers: rwbarton, thomie GHC Trac Issues: #10600 Differential Revision: https://phabricator.haskell.org/D3542 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 5 20:12:53 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 05 Jun 2017 20:12:53 -0000 Subject: [GHC] #13789: Look into haddock performance regressions due to desugaring on -fno-code Message-ID: <046.0f3a5eea19c5bdebc2f7e950a2888eb7@haskell.org> #13789: Look into haddock performance regressions due to desugaring on -fno-code -------------------------------------+------------------------------------- Reporter: bgamari | Owner: (none) Type: task | Status: new Priority: normal | Milestone: 8.4.1 Component: Compiler | Version: 8.0.1 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- c9eb4385aad248118650725b7b699bb97ee21c0d enabled desugaring when GHC is invoked with `-fno-code` in order to resolve #10600. Unfortunately this causes GHC to do more (unnecessary) work when parsing for haddock, causing some rather significant allocations regressions in the haddock performance tests, {{{ bytes allocated value is too high: Expected haddock.base(normal) bytes allocated: 25592972912 +/-5% Lower bound haddock.base(normal) bytes allocated: 24313324266 Upper bound haddock.base(normal) bytes allocated: 26872621558 Actual haddock.base(normal) bytes allocated: 27868466432 Deviation haddock.base(normal) bytes allocated: 8.9 % *** unexpected stat test failure for haddock.base(normal) =====> haddock.Cabal(normal) 6 of 7 [0, 0, 0] bytes allocated value is too high: Expected haddock.Cabal(normal) bytes allocated: 18269309128 +/-5% Lower bound haddock.Cabal(normal) bytes allocated: 17355843671 Upper bound haddock.Cabal(normal) bytes allocated: 19182774585 Actual haddock.Cabal(normal) bytes allocated: 22294859000 Deviation haddock.Cabal(normal) bytes allocated: 22.0 % *** unexpected stat test failure for haddock.Cabal(normal) =====> haddock.compiler(normal) 7 of 7 [0, 0, 0] bytes allocated value is too high: Expected haddock.compiler(normal) bytes allocated: 52762752968 +/-10% Lower bound haddock.compiler(normal) bytes allocated: 47486477671 Upper bound haddock.compiler(normal) bytes allocated: 58039028265 Actual haddock.compiler(normal) bytes allocated: 65378619232 Deviation haddock.compiler(normal) bytes allocated: 23.9 % *** unexpected stat test failure for haddock.compiler(normal) }}} Work out how to mitigate this. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 5 20:13:50 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 05 Jun 2017 20:13:50 -0000 Subject: [GHC] #10600: -fwarn-incomplete-patterns doesn't work with -fno-code In-Reply-To: <043.972d3170891da80a4e96bca7b675a836@haskell.org> References: <043.972d3170891da80a4e96bca7b675a836@haskell.org> Message-ID: <058.ab3f12d418836009757ff8073d616983@haskell.org> #10600: -fwarn-incomplete-patterns doesn't work with -fno-code -------------------------------------+------------------------------------- Reporter: akio | Owner: ezyang Type: bug | Status: closed Priority: normal | Milestone: 8.4.1 Component: Compiler | Version: 7.10.1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple warning at compile-time | Test Case: driver/T8101b Blocked By: | Blocking: Related Tickets: #8101 | Differential Rev(s): Phab:D1278 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => closed * resolution: => fixed -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 5 20:22:35 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 05 Jun 2017 20:22:35 -0000 Subject: [GHC] #13775: Type family expansion is too lazy, allows accepting of ill-typed terms In-Reply-To: <045.09c124a40b32f046227808df7e0aa665@haskell.org> References: <045.09c124a40b32f046227808df7e0aa665@haskell.org> Message-ID: <060.a5dde4243c58b36b48fb0db024d95910@haskell.org> #13775: Type family expansion is too lazy, allows accepting of ill-typed terms -------------------------------------+------------------------------------- Reporter: fizruk | Owner: diatchki Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.2 checker) | Keywords: Resolution: | CustomTypeErrors Operating System: Unknown/Multiple | Architecture: Type of failure: GHC accepts | Unknown/Multiple invalid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): > I think that this is more a question about how type functions work, rather than TypeError specifically. No, I don't think it is. GHC ''never'' reports an error simply becuase it tries to evaluate `TypeError ..`. Rather, that call is stuck. That in turn may mean that some constraint can't be solved. And then, when reporting unsolved constraints, GHC looks for any nested calls to `TypeError` and reports them rather than the constraint itself. You wrote this code! It's nothing to do with how much reduction takes place, IMHO. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 5 20:36:00 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 05 Jun 2017 20:36:00 -0000 Subject: [GHC] #11785: Kinds should be treated like types in TcSplice In-Reply-To: <047.bfff5ba2980e2ce458e592d1077c3dd1@haskell.org> References: <047.bfff5ba2980e2ce458e592d1077c3dd1@haskell.org> Message-ID: <062.ee8944fba603f54fc23823780ade19ff@haskell.org> #11785: Kinds should be treated like types in TcSplice -------------------------------------+------------------------------------- Reporter: goldfire | Owner: (none) Type: task | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 8.1 Resolution: | Keywords: TypeInType Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by goldfire): * keywords: => TypeInType -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 5 20:42:27 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 05 Jun 2017 20:42:27 -0000 Subject: [GHC] #13789: Look into haddock performance regressions due to desugaring on -fno-code In-Reply-To: <046.0f3a5eea19c5bdebc2f7e950a2888eb7@haskell.org> References: <046.0f3a5eea19c5bdebc2f7e950a2888eb7@haskell.org> Message-ID: <061.2961e8b337868e78db40c3c42ebcfb65@haskell.org> #13789: Look into haddock performance regressions due to desugaring on -fno-code -------------------------------------+------------------------------------- Reporter: bgamari | Owner: duog Type: task | Status: new Priority: normal | Milestone: 8.4.1 Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by duog): * owner: (none) => duog * failure: None/Unknown => Compile-time performance bug Comment: Looking into this now. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 5 20:58:21 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 05 Jun 2017 20:58:21 -0000 Subject: [GHC] #13790: GHC doesn't reduce type family in kind signature unless its arm is twisted Message-ID: <050.82fd0d8f15c203df7dc458114ed0312c@haskell.org> #13790: GHC doesn't reduce type family in kind signature unless its arm is twisted -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.1-rc2 (Type checker) | Keywords: TypeInType, | Operating System: Unknown/Multiple TypeFamilies | Architecture: | Type of failure: GHC rejects Unknown/Multiple | valid program Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- Here's some code (inspired by Richard's musings [https://github.com/goldfirere/singletons/issues/150#issuecomment-306088297 here]) which typechecks with GHC 8.2.1 or HEAD: {{{#!hs {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE GADTs #-} {-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE TypeInType #-} module Bug where import Data.Kind data family Sing (a :: k) data SomeSing (k :: Type) where SomeSing :: Sing (a :: k) -> SomeSing k type family Promote k :: Type class (Promote (Demote k) ~ k) => SingKind (k :: Type) where type Demote k :: Type fromSing :: Sing (a :: k) -> Demote k toSing :: Demote k -> SomeSing k type family DemoteX (a :: k) :: Demote k type instance DemoteX (a :: Type) = Demote a type instance Promote Type = Type instance SingKind Type where type Demote Type = Type fromSing = error "fromSing Type" toSing = error "toSing Type" ----- data N = Z | S N data instance Sing (z :: N) where SZ :: Sing Z SS :: Sing n -> Sing (S n) type instance Promote N = N instance SingKind N where type Demote N = N fromSing SZ = Z fromSing (SS n) = S (fromSing n) toSing Z = SomeSing SZ toSing (S n) = case toSing n of SomeSing sn -> SomeSing (SS sn) }}} Things get more interesting if you try to add this type instance at the end of this file: {{{#!hs type instance DemoteX (n :: N) = n }}} Now GHC will complain: {{{ GHCi, version 8.2.0.20170522: http://www.haskell.org/ghc/ :? for help Loaded GHCi configuration from /home/rgscott/.ghci [1 of 1] Compiling Bug ( Bug.hs, interpreted ) Bug.hs:49:34: error: • Expected kind ‘Demote N’, but ‘n’ has kind ‘N’ • In the type ‘n’ In the type instance declaration for ‘DemoteX’ | 49 | type instance DemoteX (n :: N) = n | ^ }}} That error message smells funny, since we do have a type family instance that says `Demote N = N`! In fact, if you use Template Haskell to split up the declarations manually: {{{#!hs ... instance SingKind N where type Demote N = N fromSing SZ = Z fromSing (SS n) = S (fromSing n) toSing Z = SomeSing SZ toSing (S n) = case toSing n of SomeSing sn -> SomeSing (SS sn) $(return []) type instance DemoteX (n :: N) = n }}} Then the file typechecks without issue. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 5 21:01:00 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 05 Jun 2017 21:01:00 -0000 Subject: [GHC] #13775: Type family expansion is too lazy, allows accepting of ill-typed terms In-Reply-To: <045.09c124a40b32f046227808df7e0aa665@haskell.org> References: <045.09c124a40b32f046227808df7e0aa665@haskell.org> Message-ID: <060.945095ad71249a168555ed2d7a29eb93@haskell.org> #13775: Type family expansion is too lazy, allows accepting of ill-typed terms -------------------------------------+------------------------------------- Reporter: fizruk | Owner: diatchki Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.2 checker) | Keywords: Resolution: | CustomTypeErrors Operating System: Unknown/Multiple | Architecture: Type of failure: GHC accepts | Unknown/Multiple invalid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by diatchki): I remember how the implementation works. My comment was about the fact that GHC is perfectly happy to treat "stuck" types as ordinary types without fully resolving them, which is why it can solve constraints such as `Show (Proxy (TypeError ...))`, or `Show (Proxy (F Int))`. A different design choice is to refuse to solve such constraints until GHC is sure that the type functions involved will produce a valid result, but that's not what we currently do. As a result, neither the `TypeError` nor the missing `F Int` instance are reported, and the `Show` constraint is happily solved, which is---perhaps---somewhat confusing. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 5 21:07:56 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 05 Jun 2017 21:07:56 -0000 Subject: [GHC] #11962: Support induction recursion In-Reply-To: <047.045273ef2ac55a0385e215af795b4757@haskell.org> References: <047.045273ef2ac55a0385e215af795b4757@haskell.org> Message-ID: <062.30715a42e7e170027f2d412ce18d2240@haskell.org> #11962: Support induction recursion -------------------------------------+------------------------------------- Reporter: goldfire | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.1 Resolution: | Keywords: TypeInType Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by goldfire): * keywords: => TypeInType -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 5 21:12:34 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 05 Jun 2017 21:12:34 -0000 Subject: [GHC] #13790: GHC doesn't reduce type family in kind signature unless its arm is twisted In-Reply-To: <050.82fd0d8f15c203df7dc458114ed0312c@haskell.org> References: <050.82fd0d8f15c203df7dc458114ed0312c@haskell.org> Message-ID: <065.e8e2d8a0e4c2f6092e304c6d5ed0024d@haskell.org> #13790: GHC doesn't reduce type family in kind signature unless its arm is twisted -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.2.1-rc2 checker) | Keywords: TypeInType, Resolution: | TypeFamilies Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by goldfire): Could this be a concrete example that tickles the problems discussed in #12088? Perhaps. Either that, or the fix for #11348 didn't go far enough. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jun 6 00:11:43 2017 From: ghc-devs at haskell.org (GHC) Date: Tue, 06 Jun 2017 00:11:43 -0000 Subject: [GHC] #13786: GHCi linker is dependent upon object file order In-Reply-To: <047.0a99d83942bb8bb77d0420502e27819e@haskell.org> References: <047.0a99d83942bb8bb77d0420502e27819e@haskell.org> Message-ID: <062.6b663efd86d2f9602cd5017c709cfd5e@haskell.org> #13786: GHCi linker is dependent upon object file order -------------------------------------+------------------------------------- Reporter: ppelleti | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Runtime System | Version: 8.0.2 (Linker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): Actually, I hadn't previously noticed that the error isn't from the runtime linker at all. Rather, it is from `dlopen`. It seems that we are linking each individual object file into a separate shared library and `dlopen`ing them individually. Why? Well, I don't know, but it sure seems silly. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jun 6 02:26:05 2017 From: ghc-devs at haskell.org (GHC) Date: Tue, 06 Jun 2017 02:26:05 -0000 Subject: [GHC] #12710: Make some reserved Unicode symbols "specials" In-Reply-To: <051.88b8e9f391a6c7d6ea42931dc5feec1e@haskell.org> References: <051.88b8e9f391a6c7d6ea42931dc5feec1e@haskell.org> Message-ID: <066.b39db61b356ab28e9c6bb4c1a5c2e8a3@haskell.org> #12710: Make some reserved Unicode symbols "specials" -------------------------------------+------------------------------------- Reporter: JoshPrice247 | Owner: (none) Type: feature request | Status: new Priority: low | Milestone: Component: Compiler | Version: 8.0.1 (Parser) | Keywords: Unicode, Resolution: | UnicodeSyntax Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by JoshPrice247): * owner: JoshPrice247 => (none) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jun 6 03:02:45 2017 From: ghc-devs at haskell.org (GHC) Date: Tue, 06 Jun 2017 03:02:45 -0000 Subject: [GHC] #13644: overloaded name used in record pattern matching leads to panic! (the 'impossible' happened) in ghc In-Reply-To: <049.42fb65c94c9d58534f92e7ad520e593b@haskell.org> References: <049.42fb65c94c9d58534f92e7ad520e593b@haskell.org> Message-ID: <064.27d111e0697b757052d7271767d3f272@haskell.org> #13644: overloaded name used in record pattern matching leads to panic! (the 'impossible' happened) in ghc -------------------------------------+------------------------------------- Reporter: pjljvdlaar | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by Phyx-): * os: Windows => Unknown/Multiple -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jun 6 04:28:39 2017 From: ghc-devs at haskell.org (GHC) Date: Tue, 06 Jun 2017 04:28:39 -0000 Subject: [GHC] #13703: Internal libraries regression in GHC 8.2 (ghc-pkg handling) In-Reply-To: <045.0eb24a47df9920808d8c257fd8ac90fc@haskell.org> References: <045.0eb24a47df9920808d8c257fd8ac90fc@haskell.org> Message-ID: <060.2da759c701dd1d037eb334736898b3f5@haskell.org> #13703: Internal libraries regression in GHC 8.2 (ghc-pkg handling) -------------------------------------+------------------------------------- Reporter: ezyang | Owner: ezyang Type: bug | Status: new Priority: highest | Milestone: 8.2.1 Component: ghc-pkg | Version: 8.2.1-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3590 Wiki Page: | -------------------------------------+------------------------------------- Comment (by ezyang): Nope, the remaining test failures are actually all just wobbliness in test suite. This bug is fixed! -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jun 6 04:28:52 2017 From: ghc-devs at haskell.org (GHC) Date: Tue, 06 Jun 2017 04:28:52 -0000 Subject: [GHC] #13703: Internal libraries regression in GHC 8.2 (ghc-pkg handling) In-Reply-To: <045.0eb24a47df9920808d8c257fd8ac90fc@haskell.org> References: <045.0eb24a47df9920808d8c257fd8ac90fc@haskell.org> Message-ID: <060.ad53bb63637c5f28214af3246a7dcfed@haskell.org> #13703: Internal libraries regression in GHC 8.2 (ghc-pkg handling) -------------------------------------+------------------------------------- Reporter: ezyang | Owner: ezyang Type: bug | Status: closed Priority: highest | Milestone: 8.2.1 Component: ghc-pkg | Version: 8.2.1-rc2 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3590 Wiki Page: | -------------------------------------+------------------------------------- Changes (by ezyang): * status: new => closed * resolution: => fixed -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jun 6 09:58:49 2017 From: ghc-devs at haskell.org (GHC) Date: Tue, 06 Jun 2017 09:58:49 -0000 Subject: [GHC] #13790: GHC doesn't reduce type family in kind signature unless its arm is twisted In-Reply-To: <050.82fd0d8f15c203df7dc458114ed0312c@haskell.org> References: <050.82fd0d8f15c203df7dc458114ed0312c@haskell.org> Message-ID: <065.b766addaa2292edaa7a3ad5de68f6c00@haskell.org> #13790: GHC doesn't reduce type family in kind signature unless its arm is twisted -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.2.1-rc2 checker) | Keywords: TypeInType, Resolution: | TypeFamilies Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): To me it looks just lie #12088. To which I think we have a plan but it needs execution. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jun 6 09:59:20 2017 From: ghc-devs at haskell.org (GHC) Date: Tue, 06 Jun 2017 09:59:20 -0000 Subject: [GHC] #12088: Type/data family instances in kind checking In-Reply-To: <048.155fdb7e7ce6e09c92258c376a6950ab@haskell.org> References: <048.155fdb7e7ce6e09c92258c376a6950ab@haskell.org> Message-ID: <063.fb90db734491ea89abb07bff479259c2@haskell.org> #12088: Type/data family instances in kind checking -------------------------------------+------------------------------------- Reporter: alexvieth | Owner: (none) Type: bug | Status: new Priority: high | Milestone: 8.4.1 Component: Compiler (Type | Version: 8.1 checker) | Resolution: | Keywords: TypeInType Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: #11348, #12239, | Differential Rev(s): Phab:D2272 #12643, #13790 | Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * related: #11348, #12239, #12643 => #11348, #12239, #12643, #13790 Comment: See also #13790 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jun 6 10:24:46 2017 From: ghc-devs at haskell.org (GHC) Date: Tue, 06 Jun 2017 10:24:46 -0000 Subject: [GHC] #11962: Support induction recursion In-Reply-To: <047.045273ef2ac55a0385e215af795b4757@haskell.org> References: <047.045273ef2ac55a0385e215af795b4757@haskell.org> Message-ID: <062.a25be82c2ba06c9df8430bd1a4fcde86@haskell.org> #11962: Support induction recursion -------------------------------------+------------------------------------- Reporter: goldfire | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.1 Resolution: | Keywords: TypeInType Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by Iceland_jack): * cc: Iceland_jack (added) Comment: TODO Add GHC to [https://en.wikipedia.org/wiki/Induction-recursion#Usage Wikipedia] when implemented ;) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jun 6 11:08:38 2017 From: ghc-devs at haskell.org (GHC) Date: Tue, 06 Jun 2017 11:08:38 -0000 Subject: [GHC] #13791: Document allowed syntax in WARNING and DEPRECATED pragmas Message-ID: <046.d7785f3c9a9f9afccfdc542d40ba4787@haskell.org> #13791: Document allowed syntax in WARNING and DEPRECATED pragmas -------------------------------------+------------------------------------- Reporter: phischu | Owner: (none) Type: bug | Status: new Priority: lowest | Milestone: Component: Compiler | Version: 8.0.2 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: Documentation Unknown/Multiple | bug Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- GHC accepts the following deprecation pragma: {{{#!hs {-# DEPRECATED f ["f is deprecated","use g instead"] #-} f :: a -> a f x = x }}} The deprecation message here is a list of strings. I didn't expect this to be allowed because [https://downloads.haskell.org/~ghc/latest/docs/html/users_guide/glasgow_exts.html #warning-and-deprecated-pragmas] only shows examples where the deprecation message is a single string. Are there other forms of deprecation message allowed by GHC? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jun 6 12:10:21 2017 From: ghc-devs at haskell.org (GHC) Date: Tue, 06 Jun 2017 12:10:21 -0000 Subject: [GHC] #13608: Expose the type of quasiquotes In-Reply-To: <056.25d1d92a9495f18e85d0ecacba264382@haskell.org> References: <056.25d1d92a9495f18e85d0ecacba264382@haskell.org> Message-ID: <071.e540f79705bd9576741ab139db169e73@haskell.org> #13608: Expose the type of quasiquotes -------------------------------------+------------------------------------- Reporter: | Owner: facundo.dominguez | facundo.dominguez Type: bug | Status: patch Priority: normal | Milestone: Component: Template Haskell | Version: 8.0.1 Resolution: | Keywords: QuasiQuotes Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: 12778 | Differential Rev(s): Phab:D3610 Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): > Looks like typed splices and quasiquotes will pose some gotchas. Ah, yes, I understand what's happening here, and (once again) it's awkward. GHC has to compile ''and run'' the term inside the splice, here `$$(q)`. But since `q :: forall a. C a => Q (TExp a)`, looking at `$$(q)` in isolation we just see that `q` has type `Q (TExp alpha)` with constraint `C alpha`, but we don't know what `alpha` is. It'll ultimately be fixed by the `asTypeOf (0::Int)` part, but not yet. If you change it to `$$(q) :: Int` then it does work because the information about the `Int` type is pushed inwards from the type signature. That is horribly delicate, and I had not realised it before. The robust way to do it would be `$$(q :: Q (TExp Int))`, putting all the type info inside the splice. This doesn't happen for untyped splices because they don't expect to get any type info from the context. I think I should probably ''stop'' pushing type info from the context into a typed splice, so that it would fail reliably. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jun 6 12:19:17 2017 From: ghc-devs at haskell.org (GHC) Date: Tue, 06 Jun 2017 12:19:17 -0000 Subject: [GHC] #13608: Expose the type of quasiquotes In-Reply-To: <056.25d1d92a9495f18e85d0ecacba264382@haskell.org> References: <056.25d1d92a9495f18e85d0ecacba264382@haskell.org> Message-ID: <071.3521686da840ae2a2bde15e437a0a35f@haskell.org> #13608: Expose the type of quasiquotes -------------------------------------+------------------------------------- Reporter: | Owner: facundo.dominguez | facundo.dominguez Type: bug | Status: patch Priority: normal | Milestone: Component: Template Haskell | Version: 8.0.1 Resolution: | Keywords: QuasiQuotes Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: 12778 | Differential Rev(s): Phab:D3610 Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): > I don't submit a GHC proposal because we don't have yet a good solution to propose Indeed. And I don't feel comfortable about any of the solutions you propose, because they all feel so specific and ad-hoc. Is there anything we could do to have a more basic mechanism that is also more flexible? It seems that, for a given top-level splice (or quasiquote), you want to have the opportunity to do some arbitrary work "later", when type checking is complete; a bit like a core-to-core pass that works through those splices. Suppose you could say {{{ addPostProcessor :: (CoreExpr -> IO (CoreExpr, [CoreBind])) -> Q () }}} So `addPostProcessor f` would say * When type checking and desugaring is complete, please run `f` on the spliced-in expression. * `f e` will return a new expression (of the same type) to replace it with (often just `e`). * ...and perhaps some new top-level bindings. The nice thing about this is that when we are in Core every `Id` has its type "inside" it; we don't need to consult any type environment etc, which has given us a lot of trouble with the `addModFinaliser` stuff (which this would replace). Just thinking aloud. I don't want us to get stuck in a deeper and deeper pile of sticking plasters. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jun 6 12:27:49 2017 From: ghc-devs at haskell.org (GHC) Date: Tue, 06 Jun 2017 12:27:49 -0000 Subject: [GHC] #13775: Type family expansion is too lazy, allows accepting of ill-typed terms In-Reply-To: <045.09c124a40b32f046227808df7e0aa665@haskell.org> References: <045.09c124a40b32f046227808df7e0aa665@haskell.org> Message-ID: <060.391411e8d3c85d888ff365acc6f9210d@haskell.org> #13775: Type family expansion is too lazy, allows accepting of ill-typed terms -------------------------------------+------------------------------------- Reporter: fizruk | Owner: diatchki Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.2 checker) | Keywords: Resolution: | CustomTypeErrors Operating System: Unknown/Multiple | Architecture: Type of failure: GHC accepts | Unknown/Multiple invalid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): Sorry -- I didn't mean to sound snarky! > A different design choice is to refuse to solve such constraints until GHC is sure that the type functions involved will produce a valid result I think you are suggesting that * Don't do any work on a constraint that mentions `TypeError`. E.g. `C [TypeError ..]` would never be solved, regardless of the instances for `C`. That sounds attractive, but it's fragile. Suppose we had `[W] C [alpha]` where `alpha` is a unification variable. Can we use an instance declaration on that? Well, no; it might turn out that, after hundreds more simplification steps on other constraints mentioning `alpha`, that `alpha := TypeError...`. Or it might be `[W] C (F alpha)`, where eventually `alpha := Int`, and then we reduce `F Int` to `TypeError...`. So I don't see how to make this approach robustly implementable. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jun 6 13:15:03 2017 From: ghc-devs at haskell.org (GHC) Date: Tue, 06 Jun 2017 13:15:03 -0000 Subject: [GHC] #12778: Expose variables bound in quotations to reify In-Reply-To: <056.ae7347f3834b6f538314d4417b60f405@haskell.org> References: <056.ae7347f3834b6f538314d4417b60f405@haskell.org> Message-ID: <071.2076391ced112e0a6b8d858c25732d2d@haskell.org> #12778: Expose variables bound in quotations to reify -------------------------------------+------------------------------------- Reporter: | Owner: (none) facundo.dominguez | Type: bug | Status: patch Priority: normal | Milestone: Component: Template Haskell | Version: 8.0.1 Resolution: | Keywords: template- | haskell reify Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3003 Wiki Page: | -------------------------------------+------------------------------------- Comment (by facundo.dominguez): Another way to address this. We make {{{ $([| let x = True in $(q) |]) }}} desugar to {{{ $(return (LetE [ x = True ] (Splice q))) }}} where `Splice :: Q Exp -> Exp` is a new constructor of the datatype `Language.Haskell.TH.Syntax.Exp`. The compiler runs first the outer splice which becomes {{{ let x = True in $(q) }}} and then it runs the inner splice $(q) as if it were a regular top-level splice. Pros: It makes inner splices work pretty much as outer splices. Cons: This probably is a bigger change in the compiler (hopefully not too big). -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jun 6 13:16:31 2017 From: ghc-devs at haskell.org (GHC) Date: Tue, 06 Jun 2017 13:16:31 -0000 Subject: [GHC] #13608: Expose the type of quasiquotes In-Reply-To: <056.25d1d92a9495f18e85d0ecacba264382@haskell.org> References: <056.25d1d92a9495f18e85d0ecacba264382@haskell.org> Message-ID: <071.744520e61f542d8453ef3c0838423a7d@haskell.org> #13608: Expose the type of quasiquotes -------------------------------------+------------------------------------- Reporter: | Owner: facundo.dominguez | facundo.dominguez Type: bug | Status: patch Priority: normal | Milestone: Component: Template Haskell | Version: 8.0.1 Resolution: | Keywords: QuasiQuotes Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: 12778 | Differential Rev(s): Phab:D3610 Wiki Page: | -------------------------------------+------------------------------------- Comment (by facundo.dominguez): > `addPostProcessor :: (CoreExpr -> IO (CoreExpr, [CoreBind])) -> Q ()` Will this require linking ghc with the application? `CoreExpr` and `CoreBind` are not exposed in a leaner library AFAIK. If it were not for this problem, it could be useful. Only the compiler needs to execute this code, so perhaps there is a way. I just proposed an alternative in https://ghc.haskell.org/trac/ghc/ticket/12778#comment:11 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jun 6 13:51:59 2017 From: ghc-devs at haskell.org (GHC) Date: Tue, 06 Jun 2017 13:51:59 -0000 Subject: [GHC] #12778: Expose variables bound in quotations to reify In-Reply-To: <056.ae7347f3834b6f538314d4417b60f405@haskell.org> References: <056.ae7347f3834b6f538314d4417b60f405@haskell.org> Message-ID: <071.ce96761303d916d90a0e4cad2775d800@haskell.org> #12778: Expose variables bound in quotations to reify -------------------------------------+------------------------------------- Reporter: | Owner: (none) facundo.dominguez | Type: bug | Status: patch Priority: normal | Milestone: Component: Template Haskell | Version: 8.0.1 Resolution: | Keywords: template- | haskell reify Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3003 Wiki Page: | -------------------------------------+------------------------------------- Comment (by facundo.dominguez): Regarding the previous proposal, some code might break because this code {{{ do exp <- q [| let x = True in $(return exp) |] }}} stops being equivalent to {{{[| let x = True in $(q) |]}}}. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jun 6 14:31:34 2017 From: ghc-devs at haskell.org (GHC) Date: Tue, 06 Jun 2017 14:31:34 -0000 Subject: [GHC] #8809: Prettier error messages? In-Reply-To: <047.4dbdad421fcd945584d210433034ccb5@haskell.org> References: <047.4dbdad421fcd945584d210433034ccb5@haskell.org> Message-ID: <062.aa876b97cbda50218bcec74b92c1a846@haskell.org> #8809: Prettier error messages? -------------------------------------+------------------------------------- Reporter: joelteon | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.9 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: 13122 Related Tickets: | Differential Rev(s): #8809,#10073,#10179,#12906,#13670 | Wiki Page: | -------------------------------------+------------------------------------- @@ -0,0 +1,2 @@ + [wiki:PrettyErrors] is a wiki page summarising the state of play. + New description: [wiki:PrettyErrors] is a wiki page summarising the state of play. `clang` has very nice-looking error messages. {{{ #!html
pretty.c:6:7: warning: incompatible pointer to integer conversion passing
 'char [14]' to parameter of type 'int' [-Wint-conversion]
   foo("Hello, world!");
       ^~~~~~~~~~~~~~~
 pretty.c:1:14: note: passing argument to
 parameter 'i' here
 void foo(int i) {
              ^
 1 warning generated.
}}} `ghc`'s error messages are not so good. {{{ #!html
ugly.hs:7:18:
     Couldn't match expected type ‘()’ with actual type
 ‘[Char]’
     In the first argument of ‘f’, namely ‘"Hello,
 world!"’
     In the second argument of ‘($)’, namely ‘f "Hello,
 world!"’
     In the expression: print $ f "Hello, world!"
}}} In my opinion, there are three independent improvements that could be made to GHC error messages and warnings: color, context and whitespace. Currently they're blobs of text. Consider all three applied to error messages: {{{ #!html
ugly.hs:7:18: error: Argument
 to 'f' is type '[Char]' but expected 'Int'
 main = print $ f "Hello, world!"
                  ^~~~~~~~~~~~~~~

 ugly.hs:3:1: note: type of 'f' is given here:
 f :: () -> IO ()
      ^~
}}} or {{{ #!html
ugly.hs: note: type of 'f' is inferred:
 f :: forall m. Monad m => () -> m ()
                           ^~
}}} In my opinion, context and whitespace are more important that color. Even without color, compare this error message to the one shown above: {{{ ugly.hs:7:18: error: Argument to 'f' is type '[Char]' but expected 'Int' main = print $ f "Hello, world!" ^~~~~~~~~~~~~~~ ugly.hs:3:1: note: type of 'f' is given here: f :: () -> IO () ^~ }}} In my opinion this is much easier to visually process than GHC's current messages. -- Comment (by simonpj): [wiki:PrettyErrors] is a wiki page summarising the state of play. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jun 6 14:53:43 2017 From: ghc-devs at haskell.org (GHC) Date: Tue, 06 Jun 2017 14:53:43 -0000 Subject: [GHC] #13429: Optimizer produces Core with an infinite <> In-Reply-To: <045.cf5ba15167896826f7f0c0a59d69b609@haskell.org> References: <045.cf5ba15167896826f7f0c0a59d69b609@haskell.org> Message-ID: <060.20746aa20104ca6f8d98f5e08a346824@haskell.org> #13429: Optimizer produces Core with an infinite <> -------------------------------------+------------------------------------- Reporter: lehins | Owner: (none) Type: bug | Status: new Priority: highest | Milestone: 8.2.1 Component: Compiler | Version: 8.0.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Runtime crash | Test Case: Blocked By: | Blocking: Related Tickets: #13750 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * priority: high => highest * milestone: 7.10.4 => 8.2.1 Comment: This is a bad bug, and the `FingerTree` example is still happening in HEAD, so I assume also in 8.2. (Previously it was only happening in 8.0.) I know what is going on but have been struggling to find time to fix it. Hopefully this week. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jun 6 14:54:32 2017 From: ghc-devs at haskell.org (GHC) Date: Tue, 06 Jun 2017 14:54:32 -0000 Subject: [GHC] #13429: Optimizer produces Core with an infinite <> In-Reply-To: <045.cf5ba15167896826f7f0c0a59d69b609@haskell.org> References: <045.cf5ba15167896826f7f0c0a59d69b609@haskell.org> Message-ID: <060.7fb58a5c529df7ddba7afd8b99215b45@haskell.org> #13429: Optimizer produces Core with an infinite <> -------------------------------------+------------------------------------- Reporter: lehins | Owner: simonpj Type: bug | Status: new Priority: highest | Milestone: 8.2.1 Component: Compiler | Version: 8.0.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Runtime crash | Test Case: Blocked By: | Blocking: Related Tickets: #13750 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * owner: (none) => simonpj -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jun 6 15:02:06 2017 From: ghc-devs at haskell.org (GHC) Date: Tue, 06 Jun 2017 15:02:06 -0000 Subject: [GHC] #13594: Typechecker behavior w.r.t. BangPatterns and nested foralls has changed in 8.2 In-Reply-To: <050.d768cbcd7afd3c7633840a8a13d3da1c@haskell.org> References: <050.d768cbcd7afd3c7633840a8a13d3da1c@haskell.org> Message-ID: <065.ae3a42f6b6d9d8c01774bb3dedc6172c@haskell.org> #13594: Typechecker behavior w.r.t. BangPatterns and nested foralls has changed in 8.2 -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: bgamari Type: bug | Status: new Priority: high | Milestone: 8.2.1 Component: Compiler (Type | Version: 8.2.1-rc2 checker) | Keywords: BangPatterns, Resolution: | RankNTypes Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3525 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * owner: (none) => bgamari -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jun 6 15:09:38 2017 From: ghc-devs at haskell.org (GHC) Date: Tue, 06 Jun 2017 15:09:38 -0000 Subject: [GHC] #13608: Expose the type of quasiquotes In-Reply-To: <056.25d1d92a9495f18e85d0ecacba264382@haskell.org> References: <056.25d1d92a9495f18e85d0ecacba264382@haskell.org> Message-ID: <071.9b5c0f3edd28c0a4f6644c1a09bfc56a@haskell.org> #13608: Expose the type of quasiquotes -------------------------------------+------------------------------------- Reporter: | Owner: facundo.dominguez | facundo.dominguez Type: bug | Status: patch Priority: normal | Milestone: Component: Template Haskell | Version: 8.0.1 Resolution: | Keywords: QuasiQuotes Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: 12778 | Differential Rev(s): Phab:D3610 Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): > Will this require linking ghc with the application? Ah yes, I suppose it would. Would that matter? I suppose it'd make the binary bigger. I suppose that one could imagine modules that guarantee to contain only compile-time code, and hence which do not need to be linked into the final executable. Keep thinking! I'm seeking a single, simple mechanism that'll solve multiple problems at once. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jun 6 15:14:45 2017 From: ghc-devs at haskell.org (GHC) Date: Tue, 06 Jun 2017 15:14:45 -0000 Subject: [GHC] #12778: Expose variables bound in quotations to reify In-Reply-To: <056.ae7347f3834b6f538314d4417b60f405@haskell.org> References: <056.ae7347f3834b6f538314d4417b60f405@haskell.org> Message-ID: <071.199de8c87baf46ef3b2b9ef7f6bb832d@haskell.org> #12778: Expose variables bound in quotations to reify -------------------------------------+------------------------------------- Reporter: | Owner: (none) facundo.dominguez | Type: bug | Status: patch Priority: normal | Milestone: Component: Template Haskell | Version: 8.0.1 Resolution: | Keywords: template- | haskell reify Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3003 Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): But see #13608 comment:15 and following, for an idea that might submsume this (distressingly complicated) ticket. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jun 6 15:21:27 2017 From: ghc-devs at haskell.org (GHC) Date: Tue, 06 Jun 2017 15:21:27 -0000 Subject: [GHC] #13666: The gcc wrapper can't handle trailing backslashes In-Reply-To: <046.48bb815bdf014d4f8613c4501cc5c3f5@haskell.org> References: <046.48bb815bdf014d4f8613c4501cc5c3f5@haskell.org> Message-ID: <061.97e851bbf122ecd2aea8bf561382224a@haskell.org> #13666: The gcc wrapper can't handle trailing backslashes ---------------------------------+---------------------------------------- Reporter: niklasl | Owner: (none) Type: bug | Status: patch Priority: low | Milestone: Component: Driver | Version: 8.0.1 Resolution: | Keywords: Operating System: Windows | Architecture: Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #13709 | Differential Rev(s): Phab:D3628 Wiki Page: | ---------------------------------+---------------------------------------- Changes (by Phyx-): * differential: => Phab:D3628 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jun 6 17:39:05 2017 From: ghc-devs at haskell.org (GHC) Date: Tue, 06 Jun 2017 17:39:05 -0000 Subject: [GHC] #13608: Expose the type of quasiquotes In-Reply-To: <056.25d1d92a9495f18e85d0ecacba264382@haskell.org> References: <056.25d1d92a9495f18e85d0ecacba264382@haskell.org> Message-ID: <071.eea902282b3d177ef8162da7cbe4e78a@haskell.org> #13608: Expose the type of quasiquotes -------------------------------------+------------------------------------- Reporter: | Owner: facundo.dominguez | facundo.dominguez Type: bug | Status: patch Priority: normal | Milestone: Component: Template Haskell | Version: 8.0.1 Resolution: | Keywords: QuasiQuotes Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: 12778 | Differential Rev(s): Phab:D3610 Wiki Page: | -------------------------------------+------------------------------------- Comment (by facundo.dominguez): I think this proposal would stumble with the same rock that ticket:12778 and approaches (4) and (5). Given a nested splice, how do you associate it with a post-processor added with `addPostProcessor`? This approach doesn't look very different from using compiler plugins. If the user can annotate the splice location somehow, a plugin pass could spot them and complete the program. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jun 6 18:38:51 2017 From: ghc-devs at haskell.org (GHC) Date: Tue, 06 Jun 2017 18:38:51 -0000 Subject: [GHC] #13792: Allow building using distro GCC on Windows Message-ID: <044.190a71c9e96d6252e4edbb8309f5384f@haskell.org> #13792: Allow building using distro GCC on Windows ----------------------------------------+--------------------------------- Reporter: Phyx- | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: 8.4.1 Component: Build System | Version: 8.0.1 Keywords: | Operating System: Windows Architecture: Unknown/Multiple | Type of failure: None/Unknown Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: ----------------------------------------+--------------------------------- Allow the building of GHC on Windows using distro compiler (msys2) instead of using a bundled GCC. This should make testing new GCCs and binutils easier but also make it easier to build the msys2 variant of GHC. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jun 6 18:39:08 2017 From: ghc-devs at haskell.org (GHC) Date: Tue, 06 Jun 2017 18:39:08 -0000 Subject: [GHC] #13792: Allow building using distro GCC on Windows In-Reply-To: <044.190a71c9e96d6252e4edbb8309f5384f@haskell.org> References: <044.190a71c9e96d6252e4edbb8309f5384f@haskell.org> Message-ID: <059.49d79e5a15bbb953591193bc232c60a5@haskell.org> #13792: Allow building using distro GCC on Windows -------------------------------------+------------------------------------- Reporter: Phyx- | Owner: Phyx- Type: feature request | Status: new Priority: normal | Milestone: 8.4.1 Component: Build System | Version: 8.0.1 Resolution: | Keywords: Operating System: Windows | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by Phyx-): * owner: (none) => Phyx- -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jun 6 20:20:10 2017 From: ghc-devs at haskell.org (GHC) Date: Tue, 06 Jun 2017 20:20:10 -0000 Subject: [GHC] #13373: Handle long file paths on Windows In-Reply-To: <045.872d530b642536033e5f70fd0cb14d01@haskell.org> References: <045.872d530b642536033e5f70fd0cb14d01@haskell.org> Message-ID: <060.b66d378438b363af3ace9b4889bd58de@haskell.org> #13373: Handle long file paths on Windows -------------------------------------+------------------------------------- Reporter: ezyang | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: Component: libraries/base | Version: 8.1 Resolution: | Keywords: Operating System: Windows | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by joeyhess): My software is afflicted by this problem on Windows. While the manifest file approach is only a partial solution, it would be good to at least not have the problem on Windows 10. And, it seems fairly unintrusive to enable it. ghc already embeds a manifest on windows for https://ghc.haskell.org/trac/ghc/ticket/1271 , so could longPathAware be added to it? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jun 6 21:32:11 2017 From: ghc-devs at haskell.org (GHC) Date: Tue, 06 Jun 2017 21:32:11 -0000 Subject: [GHC] #13793: Simple program trips checkNurserySanity() Message-ID: <046.a36b0da0c049dac7c618bbfdc92da5ef@haskell.org> #13793: Simple program trips checkNurserySanity() -------------------------------------+------------------------------------- Reporter: niteria | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Runtime | Version: 8.3 System | Keywords: | Operating System: Unknown/Multiple Architecture: x86_64 | Type of failure: None/Unknown (amd64) | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- Error: {{{ Repro: internal error: ASSERTION FAILED: file rts/sm/Sanity.c, line 713 (GHC version 8.3.20170606 for x86_64_unknown_linux) Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug }}} Repro steps: * Add `GhcRTSWays += thr_debug` to `mk/build.mk` to build threaded debug runtime {{{ inplace/bin/ghc-stage2 -fforce-recomp -debug -rtsopts -threaded -main-is Repro Repro.hs ./Repro +RTS -A16m -DS }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jun 6 21:36:11 2017 From: ghc-devs at haskell.org (GHC) Date: Tue, 06 Jun 2017 21:36:11 -0000 Subject: [GHC] #13793: Simple program trips checkNurserySanity() In-Reply-To: <046.a36b0da0c049dac7c618bbfdc92da5ef@haskell.org> References: <046.a36b0da0c049dac7c618bbfdc92da5ef@haskell.org> Message-ID: <061.f27e4d0c573bd64ceb5ee19ea3306c0b@haskell.org> #13793: Simple program trips checkNurserySanity() -------------------------------------+------------------------------------- Reporter: niteria | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Runtime System | Version: 8.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: x86_64 | (amd64) Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by niteria): * Attachment "Repro.hs" added. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jun 6 21:36:48 2017 From: ghc-devs at haskell.org (GHC) Date: Tue, 06 Jun 2017 21:36:48 -0000 Subject: [GHC] #13793: Simple program trips checkNurserySanity() In-Reply-To: <046.a36b0da0c049dac7c618bbfdc92da5ef@haskell.org> References: <046.a36b0da0c049dac7c618bbfdc92da5ef@haskell.org> Message-ID: <061.0f8b44d8f072ccbc6bd01ddfd75b12e7@haskell.org> #13793: Simple program trips checkNurserySanity() -------------------------------------+------------------------------------- Reporter: niteria | Owner: niteria Type: bug | Status: new Priority: normal | Milestone: Component: Runtime System | Version: 8.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: x86_64 | (amd64) Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by niteria): * owner: (none) => niteria Comment: I know what the problem is, I'm just creating this ticket for visibility. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jun 6 22:16:00 2017 From: ghc-devs at haskell.org (GHC) Date: Tue, 06 Jun 2017 22:16:00 -0000 Subject: [GHC] #13794: Stack update failed Message-ID: <051.92d35dee6ed8287df904f20b337dc59e@haskell.org> #13794: Stack update failed --------------------------------------+--------------------------------- Reporter: stevenspasbo | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Build System | Version: 8.0.1 Keywords: | Operating System: MacOS X Architecture: x86_64 (amd64) | Type of failure: None/Unknown Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: --------------------------------------+--------------------------------- Stacktrace asked me to report this as a bug: {{{#!shell [1 of 1] Compiling Main ( /private/var/folders/yx/scmdmrjx25vf6y18kgl_sqvjvq5kjp/T/stack- upgrade71650/stack-1.4.0/Setup.hs, /private/var/folders/yx/scmdmrjx25vf6y18kgl_sqvjvq5kjp/T/stack- upgrade71650/stack-1.4.0/.stack- work/dist/x86_64-osx/Cabal-1.22.5.0/setup/Main.o ) Linking /private/var/folders/yx/scmdmrjx25vf6y18kgl_sqvjvq5kjp/T/stack- upgrade71650/stack-1.4.0/.stack- work/dist/x86_64-osx/Cabal-1.22.5.0/setup/setup ... Configuring stack-1.4.0... stack-1.4.0: build Preprocessing library stack-1.4.0... [ 1 of 124] Compiling Text.PrettyPrint.Leijen.Extended ( src/Text/PrettyPrint/Leijen/Extended.hs, .stack- work/dist/x86_64-osx/Cabal-1.22.5.0/build/Text/PrettyPrint/Leijen/Extended.o ) [ 2 of 124] Compiling Hackage.Security.Client.Repository.HttpLib.HttpClient ( src/Hackage/Security/Client/Repository/HttpLib/HttpClient.hs, .stack- work/dist/x86_64-osx/Cabal-1.22.5.0/build/Hackage/Security/Client/Repository/HttpLib/HttpClient.o ) [ 3 of 124] Compiling Stack.Options.ScriptParser ( src/Stack/Options/ScriptParser.hs, .stack- work/dist/x86_64-osx/Cabal-1.22.5.0/build/Stack/Options/ScriptParser.o ) [ 4 of 124] Compiling Stack.Ghci.Script ( src/Stack/Ghci/Script.hs, .stack-work/dist/x86_64-osx/Cabal-1.22.5.0/build/Stack/Ghci/Script.o ) [ 5 of 124] Compiling Stack.FileWatch ( src/Stack/FileWatch.hs, .stack- work/dist/x86_64-osx/Cabal-1.22.5.0/build/Stack/FileWatch.o ) [ 6 of 124] Compiling System.Process.PagerEditor ( src/System/Process/PagerEditor.hs, .stack- work/dist/x86_64-osx/Cabal-1.22.5.0/build/System/Process/PagerEditor.o ) [ 7 of 124] Compiling System.Process.Log ( src/System/Process/Log.hs, .stack-work/dist/x86_64-osx/Cabal-1.22.5.0/build/System/Process/Log.o ) [ 8 of 124] Compiling Paths_stack ( .stack- work/dist/x86_64-osx/Cabal-1.22.5.0/build/autogen/Paths_stack.hs, .stack- work/dist/x86_64-osx/Cabal-1.22.5.0/build/Paths_stack.o ) [ 9 of 124] Compiling Path.Find ( src/Path/Find.hs, .stack- work/dist/x86_64-osx/Cabal-1.22.5.0/build/Path/Find.o ) [ 10 of 124] Compiling Path.Extra ( src/Path/Extra.hs, .stack- work/dist/x86_64-osx/Cabal-1.22.5.0/build/Path/Extra.o ) [ 11 of 124] Compiling System.Process.Read ( src/System/Process/Read.hs, .stack-work/dist/x86_64-osx/Cabal-1.22.5.0/build/System/Process/Read.o ) ghc: panic! (the 'impossible' happened) (GHC version 7.10.3 for x86_64-apple-darwin): Loading temp shared object failed: dlopen(/var/folders/yx/scmdmrjx25vf6y18kgl_sqvjvq5kjp/T/ghc74455_0/libghc_68.dylib, 5): no suitable image found. Did find: /var/folders/yx/scmdmrjx25vf6y18kgl_sqvjvq5kjp/T/ghc74455_0/libghc_68.dylib: malformed mach-o: load commands size (50752) > 32768 Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug Completed 26 action(s). -- While building package stack-1.4.0 using: /private/var/folders/yx/scmdmrjx25vf6y18kgl_sqvjvq5kjp/T/stack- upgrade71650/stack-1.4.0/.stack- work/dist/x86_64-osx/Cabal-1.22.5.0/setup/setup --builddir=.stack- work/dist/x86_64-osx/Cabal-1.22.5.0 build lib:stack exe:stack --ghc- options " -ddump-hi -ddump-to-file" Process exited with code: ExitFailure 1 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jun 6 22:54:18 2017 From: ghc-devs at haskell.org (GHC) Date: Tue, 06 Jun 2017 22:54:18 -0000 Subject: [GHC] #13794: Stack update failed In-Reply-To: <051.92d35dee6ed8287df904f20b337dc59e@haskell.org> References: <051.92d35dee6ed8287df904f20b337dc59e@haskell.org> Message-ID: <066.029ac60b02b7000934c5e60b9016d808@haskell.org> #13794: Stack update failed ---------------------------------+-------------------------------------- Reporter: stevenspasbo | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: Component: Build System | Version: 8.0.1 Resolution: duplicate | Keywords: Operating System: MacOS X | Architecture: x86_64 (amd64) Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #12479 | Differential Rev(s): Wiki Page: | ---------------------------------+-------------------------------------- Changes (by RyanGlScott): * status: new => closed * resolution: => duplicate * related: => #12479 Comment: Thanks for the bug report. This is a duplicate of #12479, which has been fixed in GHC 8.0.2. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jun 6 23:58:14 2017 From: ghc-devs at haskell.org (GHC) Date: Tue, 06 Jun 2017 23:58:14 -0000 Subject: [GHC] #13795: :kind! is not expanding type synonyms anymore Message-ID: <045.9bd0a404a46fb5b0930c49818b8cb45d@haskell.org> #13795: :kind! is not expanding type synonyms anymore --------------------------------------+--------------------------------- Reporter: Hjulle | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.2 Keywords: | Operating System: Linux Architecture: x86_64 (amd64) | Type of failure: None/Unknown Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: --------------------------------------+--------------------------------- Given {{{#!hs type A = () :kind! A }}} Expected result: {{{#!hs A :: * = () }}} Actual result: {{{#!hs A :: * = A }}} ---- Some IRC conversation on the topic (on #ghc): {{{ 23:37 < hjulle> :kind! does not seem to expand type synonyms for me (in GHC 8.0.2), it just prints them verbatim. Does anyone else have this problem? Example: "type A = ()" ":kind! A" will print out "A :: * = A" (which is not very helpful). 23:40 < hjulle> Is this a bug? The documentation (https://downloads.haskell.org/~ghc/latest/docs/html/users_guide/ghci.html #ghci-cmd-:kind) explicitly states that :kind! should expand type synonyms, so I think yes? 23:57 < RyanGlScott> hjulle: That's absolute a bug. File a ticket! 23:57 < RyanGlScott> *absolutely 23:58 < RyanGlScott> Moreover, I know why that's happening 23:59 < RyanGlScott> Internally, :kind! uses the normalise_type function to reduce type families: http://git.haskell.org/ghc.git/blob/e77b9a2069bca9018f989d7c4f54da099e3ab215:/compiler/types/FamInstEnv.hs#l1408 23:59 < RyanGlScott> But see the comment there Day changed to 07 jun 2017 00:00 < RyanGlScott> -- Try to not to disturb type synonyms if possible 00:01 < RyanGlScott> So fixing this would just be a matter of calling coreView afterwards (which expands type synonyms) 00:02 < RyanGlScott> er, actually, expandTypeSynonyms is even better: http://git.haskell.org/ghc.git/blob/e77b9a2069bca9018f989d7c4f54da099e3ab215:/compiler/types/Type.hs#l364 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jun 7 00:31:41 2017 From: ghc-devs at haskell.org (GHC) Date: Wed, 07 Jun 2017 00:31:41 -0000 Subject: [GHC] #13789: Look into haddock performance regressions due to desugaring on -fno-code In-Reply-To: <046.0f3a5eea19c5bdebc2f7e950a2888eb7@haskell.org> References: <046.0f3a5eea19c5bdebc2f7e950a2888eb7@haskell.org> Message-ID: <061.9586d035f1b0114543c0ea7b5c83b2a8@haskell.org> #13789: Look into haddock performance regressions due to desugaring on -fno-code -------------------------------------+------------------------------------- Reporter: bgamari | Owner: duog Type: task | Status: new Priority: normal | Milestone: 8.4.1 Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by duog): This is due to haddock being run with --optghc=-dcore-lint in ./validate I've submitted a patch which resolves this by not passing -dcore-lint on to haddock. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jun 7 00:32:16 2017 From: ghc-devs at haskell.org (GHC) Date: Wed, 07 Jun 2017 00:32:16 -0000 Subject: [GHC] #13789: Look into haddock performance regressions due to desugaring on -fno-code In-Reply-To: <046.0f3a5eea19c5bdebc2f7e950a2888eb7@haskell.org> References: <046.0f3a5eea19c5bdebc2f7e950a2888eb7@haskell.org> Message-ID: <061.33cebabe9c36ca8a168b760caead6880@haskell.org> #13789: Look into haddock performance regressions due to desugaring on -fno-code -------------------------------------+------------------------------------- Reporter: bgamari | Owner: duog Type: task | Status: patch Priority: normal | Milestone: 8.4.1 Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab: D3629 Wiki Page: | -------------------------------------+------------------------------------- Changes (by duog): * status: new => patch * differential: => Phab: D3629 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jun 7 00:33:08 2017 From: ghc-devs at haskell.org (GHC) Date: Wed, 07 Jun 2017 00:33:08 -0000 Subject: [GHC] #13789: Look into haddock performance regressions due to desugaring on -fno-code In-Reply-To: <046.0f3a5eea19c5bdebc2f7e950a2888eb7@haskell.org> References: <046.0f3a5eea19c5bdebc2f7e950a2888eb7@haskell.org> Message-ID: <061.a7afce6f5695818e93b8154b54b49696@haskell.org> #13789: Look into haddock performance regressions due to desugaring on -fno-code -------------------------------------+------------------------------------- Reporter: bgamari | Owner: duog Type: task | Status: patch Priority: normal | Milestone: 8.4.1 Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3629 Wiki Page: | -------------------------------------+------------------------------------- Changes (by duog): * differential: Phab: D3629 => Phab:D3629 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jun 7 00:33:14 2017 From: ghc-devs at haskell.org (GHC) Date: Wed, 07 Jun 2017 00:33:14 -0000 Subject: [GHC] #13795: :kind! is not expanding type synonyms anymore In-Reply-To: <045.9bd0a404a46fb5b0930c49818b8cb45d@haskell.org> References: <045.9bd0a404a46fb5b0930c49818b8cb45d@haskell.org> Message-ID: <060.b58bb25ecd99b22200dbc49527cf4783@haskell.org> #13795: :kind! is not expanding type synonyms anymore -------------------------------------+------------------------------------- Reporter: Hjulle | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: GHCi | Version: 8.0.2 Resolution: | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * keywords: => newcomer * component: Compiler => GHCi * os: Linux => Unknown/Multiple * architecture: x86_64 (amd64) => Unknown/Multiple -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jun 7 00:54:02 2017 From: ghc-devs at haskell.org (GHC) Date: Wed, 07 Jun 2017 00:54:02 -0000 Subject: [GHC] #13657: Documentation: Functional dependencies by other means In-Reply-To: <043.e6a2276b874588c5228bad3b9ffdb642@haskell.org> References: <043.e6a2276b874588c5228bad3b9ffdb642@haskell.org> Message-ID: <058.d37b6abcab0428ed6c14a4ca256f78ac@haskell.org> #13657: Documentation: Functional dependencies by other means -------------------------------------+------------------------------------- Reporter: AntC | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Documentation | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Documentation | Unknown/Multiple bug | Test Case: Blocked By: | Blocking: Related Tickets: 10431 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by AntC): Replying to [comment:4 simonpj]: > > I still think the User Manual doesn't really explain the difference between SuperClass constraints vs Instance constraints. > > PS: I'm sure you are right. If you had some specific proposed text to offer, I'd gladly review and add it. That'd be the text here: https://wiki.haskell.org/GHC/SuperClass#Expressive_Power_of_SuperClass_Constraints. (You probably in the Manual wouldn't want to go so far as including the example.) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jun 7 07:48:42 2017 From: ghc-devs at haskell.org (GHC) Date: Wed, 07 Jun 2017 07:48:42 -0000 Subject: [GHC] #13795: :kind! is not expanding type synonyms anymore In-Reply-To: <045.9bd0a404a46fb5b0930c49818b8cb45d@haskell.org> References: <045.9bd0a404a46fb5b0930c49818b8cb45d@haskell.org> Message-ID: <060.a678776a78f355f79e3b57a890849bc0@haskell.org> #13795: :kind! is not expanding type synonyms anymore -------------------------------------+------------------------------------- Reporter: Hjulle | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: GHCi | Version: 8.0.2 Resolution: | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): Did `:kind!` ever expand synonyms? The user manual claims that it does, but I can see no evidence that it ever did. Do we want it to expand synonyms? I think probably yes. If so, the right spot is here in `TcRnDriver`: {{{ ; ty' <- if normalise then do { fam_envs <- tcGetFamInstEnvs ; let (_, ty') = normaliseType fam_envs Nominal ty ; return ty' } else return ty ; }}} After calling `normaliseType`, call `Type.expandTypeSynonyms`. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jun 7 09:02:20 2017 From: ghc-devs at haskell.org (GHC) Date: Wed, 07 Jun 2017 09:02:20 -0000 Subject: [GHC] #11317: Test prog003 fails with segfault on Windows (GHCi) In-Reply-To: <046.e04825e713c12f85562a518dea8fe3f3@haskell.org> References: <046.e04825e713c12f85562a518dea8fe3f3@haskell.org> Message-ID: <061.0298f4b1700ccb1d082e48fbe62b8dcb@haskell.org> #11317: Test prog003 fails with segfault on Windows (GHCi) ---------------------------------+---------------------------------------- Reporter: rdragon | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: GHCi | Version: 7.11 Resolution: | Keywords: GC Operating System: Windows | Architecture: Unknown/Multiple Type of failure: GHCi crash | Test Case: prog003 Blocked By: | Blocking: Related Tickets: #11234 #3408 | Differential Rev(s): Wiki Page: | ---------------------------------+---------------------------------------- Changes (by mnislaih): * cc: mnislaih (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jun 7 09:12:29 2017 From: ghc-devs at haskell.org (GHC) Date: Wed, 07 Jun 2017 09:12:29 -0000 Subject: [GHC] #11317: Test prog003 fails with segfault on Windows (GHCi) In-Reply-To: <046.e04825e713c12f85562a518dea8fe3f3@haskell.org> References: <046.e04825e713c12f85562a518dea8fe3f3@haskell.org> Message-ID: <061.3fe91eabc8239f3de503077c73befed5@haskell.org> #11317: Test prog003 fails with segfault on Windows (GHCi) ---------------------------------+---------------------------------------- Reporter: rdragon | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: GHCi | Version: 7.11 Resolution: | Keywords: GC Operating System: Windows | Architecture: Unknown/Multiple Type of failure: GHCi crash | Test Case: prog003 Blocked By: | Blocking: Related Tickets: #11234 #3408 | Differential Rev(s): Wiki Page: | ---------------------------------+---------------------------------------- Changes (by bmjames): * cc: bmjames (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jun 7 09:34:59 2017 From: ghc-devs at haskell.org (GHC) Date: Wed, 07 Jun 2017 09:34:59 -0000 Subject: [GHC] #11317: Test prog003 fails with segfault on Windows (GHCi) In-Reply-To: <046.e04825e713c12f85562a518dea8fe3f3@haskell.org> References: <046.e04825e713c12f85562a518dea8fe3f3@haskell.org> Message-ID: <061.15fb701629ff3579b738134a4ac3add5@haskell.org> #11317: Test prog003 fails with segfault on Windows (GHCi) ---------------------------------+---------------------------------------- Reporter: rdragon | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: GHCi | Version: 7.11 Resolution: | Keywords: GC Operating System: Windows | Architecture: Unknown/Multiple Type of failure: GHCi crash | Test Case: prog003 Blocked By: | Blocking: Related Tickets: #11234 #3408 | Differential Rev(s): Wiki Page: | ---------------------------------+---------------------------------------- Changes (by alexandersgreen): * cc: alexandersgreen (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jun 7 09:36:40 2017 From: ghc-devs at haskell.org (GHC) Date: Wed, 07 Jun 2017 09:36:40 -0000 Subject: [GHC] #11317: Test prog003 fails with segfault on Windows (GHCi) In-Reply-To: <046.e04825e713c12f85562a518dea8fe3f3@haskell.org> References: <046.e04825e713c12f85562a518dea8fe3f3@haskell.org> Message-ID: <061.f3db97b96f5d240cdf37d9c7721cda11@haskell.org> #11317: Test prog003 fails with segfault on Windows (GHCi) ---------------------------------+---------------------------------------- Reporter: rdragon | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: GHCi | Version: 7.11 Resolution: | Keywords: GC Operating System: Windows | Architecture: Unknown/Multiple Type of failure: GHCi crash | Test Case: prog003 Blocked By: | Blocking: Related Tickets: #11234 #3408 | Differential Rev(s): Wiki Page: | ---------------------------------+---------------------------------------- Changes (by meteficha): * cc: meteficha (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jun 7 09:48:43 2017 From: ghc-devs at haskell.org (GHC) Date: Wed, 07 Jun 2017 09:48:43 -0000 Subject: [GHC] #13608: Expose the type of quasiquotes In-Reply-To: <056.25d1d92a9495f18e85d0ecacba264382@haskell.org> References: <056.25d1d92a9495f18e85d0ecacba264382@haskell.org> Message-ID: <071.ea65887942f5f6aecd3ca08e951f271a@haskell.org> #13608: Expose the type of quasiquotes -------------------------------------+------------------------------------- Reporter: | Owner: facundo.dominguez | facundo.dominguez Type: bug | Status: patch Priority: normal | Milestone: Component: Template Haskell | Version: 8.0.1 Resolution: | Keywords: QuasiQuotes Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: 12778 | Differential Rev(s): Phab:D3610 Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): > Given a nested splice, how do you associate it with a post-processor Well, GHC would apply the post-procssor to the expression for the top- level splice. It would pass the expression, so no need for any other association. I don't understand the nested-splice issue. Yes, it's a bit like a plugin. But then TH splices are already a bit like a plugin: both provide code that the compiler links dynamically and runs at compile time. I'm a bit ouf of my depth. Is anyone else interested in this? Designing for a single use-case is sometimes justified, but it's better if there are more. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jun 7 10:09:02 2017 From: ghc-devs at haskell.org (GHC) Date: Wed, 07 Jun 2017 10:09:02 -0000 Subject: [GHC] #8703: Use guard pages rather than heap checks In-Reply-To: <046.cc8df1f4c44d21b3204aafaf538413fa@haskell.org> References: <046.cc8df1f4c44d21b3204aafaf538413fa@haskell.org> Message-ID: <061.0e1e93812bbc8152891af34827951ff7@haskell.org> #8703: Use guard pages rather than heap checks -------------------------------------+------------------------------------- Reporter: schyler | Owner: simonmar Type: feature request | Status: closed Priority: normal | Milestone: Component: Runtime System | Version: Resolution: wontfix | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonmar): For local minor collections, see http://simonmar.github.io/bib/papers /local-gc.pdf We didn't merge this work into the released GHC branch because the implementation was incredibly complicated and the gains were relatively small and inconsistent. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jun 7 10:12:20 2017 From: ghc-devs at haskell.org (GHC) Date: Wed, 07 Jun 2017 10:12:20 -0000 Subject: [GHC] #11317: Test prog003 fails with segfault on Windows (GHCi) In-Reply-To: <046.e04825e713c12f85562a518dea8fe3f3@haskell.org> References: <046.e04825e713c12f85562a518dea8fe3f3@haskell.org> Message-ID: <061.c670085d8e5d7122cbda1b58e63019f7@haskell.org> #11317: Test prog003 fails with segfault on Windows (GHCi) ---------------------------------+---------------------------------------- Reporter: rdragon | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: GHCi | Version: 7.11 Resolution: | Keywords: GC Operating System: Windows | Architecture: Unknown/Multiple Type of failure: GHCi crash | Test Case: prog003 Blocked By: | Blocking: Related Tickets: #11234 #3408 | Differential Rev(s): Wiki Page: | ---------------------------------+---------------------------------------- Comment (by mnislaih): We are seeing segmentation faults (in Windows only) quite regularly while trying to run things in ghci, or even just off lens TH splices while compiling code. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jun 7 10:18:24 2017 From: ghc-devs at haskell.org (GHC) Date: Wed, 07 Jun 2017 10:18:24 -0000 Subject: [GHC] #11317: Test prog003 fails with segfault on Windows (GHCi) In-Reply-To: <046.e04825e713c12f85562a518dea8fe3f3@haskell.org> References: <046.e04825e713c12f85562a518dea8fe3f3@haskell.org> Message-ID: <061.6afa25f0701aa197501f5bad22977cca@haskell.org> #11317: Test prog003 fails with segfault on Windows (GHCi) ---------------------------------+---------------------------------------- Reporter: rdragon | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: GHCi | Version: 7.11 Resolution: | Keywords: GC Operating System: Windows | Architecture: Unknown/Multiple Type of failure: GHCi crash | Test Case: prog003 Blocked By: | Blocking: Related Tickets: #11234 #3408 | Differential Rev(s): Wiki Page: | ---------------------------------+---------------------------------------- Comment (by Phyx-): Hi, do you have a small example where this occurs? prog003 is quote hard to debug due to the shell interactions. If you have a Haskell only example could you report it under a new issue? Thanks! -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jun 7 10:35:30 2017 From: ghc-devs at haskell.org (GHC) Date: Wed, 07 Jun 2017 10:35:30 -0000 Subject: [GHC] #13751: Runtime crash with <> after concurrent stressing of STM computations In-Reply-To: <046.2e620bb56fd39fe88732c85fa515dde8@haskell.org> References: <046.2e620bb56fd39fe88732c85fa515dde8@haskell.org> Message-ID: <061.c2754b5def74686fcbc09c375e768cb4@haskell.org> #13751: Runtime crash with <> after concurrent stressing of STM computations -------------------------------------+------------------------------------- Reporter: literon | Owner: simonmar Type: bug | Status: new Priority: highest | Milestone: 8.2.1 Component: Runtime System | Version: 8.0.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Runtime crash | Test Case: Blocked By: | Blocking: Related Tickets: 10414 | Differential Rev(s): Phab:D3630 Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonmar): * differential: => Phab:D3630 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jun 7 12:17:39 2017 From: ghc-devs at haskell.org (GHC) Date: Wed, 07 Jun 2017 12:17:39 -0000 Subject: [GHC] #13763: Performance regression (~34%) in 8.2.1, poor register allocation(?) in an inner loop over an array In-Reply-To: <048.3858df3b3399782d9452f01ad23b4ddd@haskell.org> References: <048.3858df3b3399782d9452f01ad23b4ddd@haskell.org> Message-ID: <063.2086690b34fdd9dbe8557448fa1af810@haskell.org> #13763: Performance regression (~34%) in 8.2.1, poor register allocation(?) in an inner loop over an array -------------------------------------+------------------------------------- Reporter: jberryman | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (NCG) | Version: 8.2.1-rc2 Resolution: | Keywords: JoinPoints Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * cc: kavon@… (added) Comment: I'm puzzled. The changes in comment:3 change `letrec` into `joinrec`, which ought to be a straight win. I'm adding Kavon in cc because he is interested in this back-end stuff. More insight into where the regression comes from would be helpful, if anyone has time to dig in. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jun 7 12:47:38 2017 From: ghc-devs at haskell.org (GHC) Date: Wed, 07 Jun 2017 12:47:38 -0000 Subject: [GHC] #13429: Optimizer produces Core with an infinite <> In-Reply-To: <045.cf5ba15167896826f7f0c0a59d69b609@haskell.org> References: <045.cf5ba15167896826f7f0c0a59d69b609@haskell.org> Message-ID: <060.86d965a075ff21900a472ef91c7e93a0@haskell.org> #13429: Optimizer produces Core with an infinite <> -------------------------------------+------------------------------------- Reporter: lehins | Owner: simonpj Type: bug | Status: new Priority: highest | Milestone: 8.2.1 Component: Compiler | Version: 8.0.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Runtime crash | Test Case: Blocked By: | Blocking: Related Tickets: #13750 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Simon Peyton Jones ): In [changeset:"2b74bd9d8b4c6b20f3e8d9ada12e7db645cc3c19/ghc" 2b74bd9d/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="2b74bd9d8b4c6b20f3e8d9ada12e7db645cc3c19" Stop the specialiser generating loopy code This patch fixes a bad bug in the specialiser, which showed up as Trac #13429. When specialising an imported DFun, the specialiser could generate a recusive loop where none existed in the original program. It's all rather tricky, and I've documented it at some length in Note [Avoiding loops] We'd encoutered exactly this before (Trac #3591) but I had failed to realise that the very same thing could happen for /imported/ DFuns. I did quite a bit of refactoring. The compiler seems to get a tiny bit faster on deriving/perf/T10858 but almost all the gain had occurred before now; this patch just pushed it over the line. }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jun 7 12:47:38 2017 From: ghc-devs at haskell.org (GHC) Date: Wed, 07 Jun 2017 12:47:38 -0000 Subject: [GHC] #3591: A working program reports <> when compiled with -O In-Reply-To: <047.0475174377feb22d7d802e2794561872@haskell.org> References: <047.0475174377feb22d7d802e2794561872@haskell.org> Message-ID: <062.d626ab00b39204a12f1221cad6c468bd@haskell.org> #3591: A working program reports <> when compiled with -O -------------------------------+------------------------------------------- Reporter: blamario | Owner: igloo Type: merge | Status: closed Priority: normal | Milestone: 6.12.1 Component: Compiler | Version: 6.10.4 Resolution: fixed | Keywords: Operating System: Linux | Architecture: x86_64 (amd64) Type of failure: | Test Case: simplCore/should_run/T3591 None/Unknown | Blocked By: | Blocking: Related Tickets: | -------------------------------+------------------------------------------- Comment (by Simon Peyton Jones ): In [changeset:"2b74bd9d8b4c6b20f3e8d9ada12e7db645cc3c19/ghc" 2b74bd9d/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="2b74bd9d8b4c6b20f3e8d9ada12e7db645cc3c19" Stop the specialiser generating loopy code This patch fixes a bad bug in the specialiser, which showed up as Trac #13429. When specialising an imported DFun, the specialiser could generate a recusive loop where none existed in the original program. It's all rather tricky, and I've documented it at some length in Note [Avoiding loops] We'd encoutered exactly this before (Trac #3591) but I had failed to realise that the very same thing could happen for /imported/ DFuns. I did quite a bit of refactoring. The compiler seems to get a tiny bit faster on deriving/perf/T10858 but almost all the gain had occurred before now; this patch just pushed it over the line. }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jun 7 13:42:02 2017 From: ghc-devs at haskell.org (GHC) Date: Wed, 07 Jun 2017 13:42:02 -0000 Subject: [GHC] #13750: GHC produces incorrect coercions in hairy code In-Reply-To: <045.2957c281e52a0617c4b44226d50f7bbc@haskell.org> References: <045.2957c281e52a0617c4b44226d50f7bbc@haskell.org> Message-ID: <060.7df6500e4fd1fabab917079e69f23785@haskell.org> #13750: GHC produces incorrect coercions in hairy code -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: (none) Type: bug | Status: new Priority: highest | Milestone: 8.2.2 Component: Compiler | Version: 8.2.1-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Runtime crash | Test Case: Blocked By: | Blocking: Related Tickets: #13429 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): Commit 2b74bd9d8b4c6b20f3e8d9ada12e7db645cc3c19 (Stop the specialiser generating loopy code), the fix for #13429, also fixed this bug! Hooray! -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jun 7 13:50:44 2017 From: ghc-devs at haskell.org (GHC) Date: Wed, 07 Jun 2017 13:50:44 -0000 Subject: [GHC] #13750: GHC produces incorrect coercions in hairy code In-Reply-To: <045.2957c281e52a0617c4b44226d50f7bbc@haskell.org> References: <045.2957c281e52a0617c4b44226d50f7bbc@haskell.org> Message-ID: <060.eaf8e624bbf5901dc94cee9f0e39f720@haskell.org> #13750: GHC produces incorrect coercions in hairy code -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: (none) Type: bug | Status: new Priority: highest | Milestone: 8.2.2 Component: Compiler | Version: 8.2.1-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Runtime crash | Test Case: Blocked By: | Blocking: Related Tickets: #13429 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by dfeuer): Replying to [comment:9 RyanGlScott]: > Commit 2b74bd9d8b4c6b20f3e8d9ada12e7db645cc3c19 (Stop the specialiser generating loopy code), the fix for #13429, also fixed this bug! Hooray! It would be very nice if one of the type gurus could come up with a story about why that change fixed this. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jun 7 13:59:08 2017 From: ghc-devs at haskell.org (GHC) Date: Wed, 07 Jun 2017 13:59:08 -0000 Subject: [GHC] #13750: GHC produces incorrect coercions in hairy code In-Reply-To: <045.2957c281e52a0617c4b44226d50f7bbc@haskell.org> References: <045.2957c281e52a0617c4b44226d50f7bbc@haskell.org> Message-ID: <060.98428c02717719a216c9d535bd4ae3e3@haskell.org> #13750: GHC produces incorrect coercions in hairy code -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: (none) Type: bug | Status: new Priority: highest | Milestone: 8.2.2 Component: Compiler | Version: 8.2.1-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Runtime crash | Test Case: Blocked By: | Blocking: Related Tickets: #13429 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): I'm no "type guru", but I find this development quite unsurprising. The "utterly bogus definition" that you pointed out in the original comment concerns the `All` type class, which has `AllF` as a superclass. The nub of #13429 concerns improper specialization of dictionary functions with superclasses, and `All` falls into the category. Combine incorrect specialization with `unsafeCoerce`, and segfaults are just around the corner. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jun 7 14:11:50 2017 From: ghc-devs at haskell.org (GHC) Date: Wed, 07 Jun 2017 14:11:50 -0000 Subject: [GHC] #13429: Optimizer produces Core with an infinite <> In-Reply-To: <045.cf5ba15167896826f7f0c0a59d69b609@haskell.org> References: <045.cf5ba15167896826f7f0c0a59d69b609@haskell.org> Message-ID: <060.07739d19b5e5a5f5ee5047dadf7e16ee@haskell.org> #13429: Optimizer produces Core with an infinite <> -------------------------------------+------------------------------------- Reporter: lehins | Owner: simonpj Type: bug | Status: merge Priority: highest | Milestone: 8.2.1 Component: Compiler | Version: 8.0.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Runtime crash | Test Case: | simplCore/should_run/T13429, | T13429_2 Blocked By: | Blocking: Related Tickets: #13750 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * testcase: => simplCore/should_run/T13429, T13429_2 * status: new => merge Comment: Worth merging I think! -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jun 7 14:15:55 2017 From: ghc-devs at haskell.org (GHC) Date: Wed, 07 Jun 2017 14:15:55 -0000 Subject: [GHC] #13750: GHC produces incorrect coercions in hairy code In-Reply-To: <045.2957c281e52a0617c4b44226d50f7bbc@haskell.org> References: <045.2957c281e52a0617c4b44226d50f7bbc@haskell.org> Message-ID: <060.03da1d69f28f7d0d6f0e1334196564c6@haskell.org> #13750: GHC produces incorrect coercions in hairy code -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: (none) Type: bug | Status: new Priority: highest | Milestone: 8.2.2 Component: Compiler | Version: 8.2.1-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Runtime crash | Test Case: Blocked By: | Blocking: Related Tickets: #13429 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Simon Peyton Jones ): In [changeset:"ef07010cf4f480d9f595a71cf5b009884522a75e/ghc" ef07010c/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="ef07010cf4f480d9f595a71cf5b009884522a75e" Test Trac #13750 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jun 7 14:17:53 2017 From: ghc-devs at haskell.org (GHC) Date: Wed, 07 Jun 2017 14:17:53 -0000 Subject: [GHC] #13750: GHC produces incorrect coercions in hairy code In-Reply-To: <045.2957c281e52a0617c4b44226d50f7bbc@haskell.org> References: <045.2957c281e52a0617c4b44226d50f7bbc@haskell.org> Message-ID: <060.1be1eb75a737116239f19d97e57f8d32@haskell.org> #13750: GHC produces incorrect coercions in hairy code -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: (none) Type: bug | Status: new Priority: highest | Milestone: 8.2.2 Component: Compiler | Version: 8.2.1-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Runtime crash | Test Case: Blocked By: | Blocking: Related Tickets: #13429 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): You may not be surprised, but I am. But I'm also delighted -- I was not looking forward to discovering what was happening. I hope that it's actually fixed, not just masked. But let's see if Andres's original problem is fixed. If it is, let's declare victory and close. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jun 7 14:59:13 2017 From: ghc-devs at haskell.org (GHC) Date: Wed, 07 Jun 2017 14:59:13 -0000 Subject: [GHC] #13796: hard to embed custom manifest on windows Message-ID: <047.a85c2b7fd2ccf64d7a50d2285d24d244@haskell.org> #13796: hard to embed custom manifest on windows ----------------------------------------+--------------------------------- Reporter: joeyhess | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.2 Keywords: | Operating System: Windows Architecture: Unknown/Multiple | Type of failure: None/Unknown Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: ----------------------------------------+--------------------------------- I want to use a custom manifest file on windows to enable long filename support. I tried several ghc options to find a way to do it, and it does not seem easily possible to do this. First I thought, let's use -fno-gen-manifest, and since ghc generates foo.exe.manifest when building foo.hs, I'll provide a file with that name and it'll pick it up. But it seems that -fno-gen-manifest implies -fno- embed-manifest, so it didn't run windres, and this didn't work. Then I tried using -optwindres, hoping to pass windres -i foo.rc, and make that file point to my custom manifest. But, despite being documented as options that are passed to windres, -optwindres actually adds to the end of the windres --preprocessor option, so this caused it to run windres --preprocessor "gcc.exe ... -i foo.rc" The only remaining option seems to be to use -pgmwindres with a wrapper program that runs windres with the options I want. It seemed easier to file a ghc bug at this point.. I feel that the best fix would be either to still run windres when -fno- gen-manifest is used, or to add a new option like -fuse-custom-manifest- file=filename -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jun 7 15:27:35 2017 From: ghc-devs at haskell.org (GHC) Date: Wed, 07 Jun 2017 15:27:35 -0000 Subject: [GHC] #13797: Mark negation injective Message-ID: <051.007a4c5e822247cfb7425a4d2f2120d0@haskell.org> #13797: Mark negation injective -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Keywords: | Operating System: Unknown/Multiple InjectiveFamilies | Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- {{{#!hs {-# Language DataKinds, TypeOperators, TypeFamilyDependencies, UndecidableInstances #-} import GHC.TypeLits data N = O | S N type family U (a :: Nat) = (res :: N) | res -> a where U 0 = O U n = S (U (n-1)) }}} gives {{{ olates injectivity annotation. Type variable ‘n’ cannot be inferred from the right-hand side. In the type family equation: U n = 'S (U (n - 1)) -- Defined at /tmp/a.hs:37:3 • In the equations for closed type family ‘U’ In the type family declaration for ‘U’ Failed, modules loaded: none. }}} I expect this to work, this depends on making `(-)` injective which depends on [https://ghc.haskell.org/trac/ghc/wiki/InjectiveTypeFamilies#Futureplansandideas "generalized injectivity"]? {{{#!hs type family (a :: Nat) - (b :: Nat) = (res :: Nat) | a b -> res, res a -> b, res b -> a where {- built in -} }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jun 7 15:30:36 2017 From: ghc-devs at haskell.org (GHC) Date: Wed, 07 Jun 2017 15:30:36 -0000 Subject: =?utf-8?b?UmU6IFtHSENdICMxMzYxNTogTm9uZGV0ZXJtaW5pc20gaW4g4oCY?= =?utf-8?q?pure=E2=80=99_function_w/_parallel_evaluation_=26_memo?= =?utf-8?q?_combinators?= In-Reply-To: <044.57733831351687fff6258688df1f42f7@haskell.org> References: <044.57733831351687fff6258688df1f42f7@haskell.org> Message-ID: <059.ac1b8f99e2ddc70a82d5c00f9b12c81e@haskell.org> #13615: Nondeterminism in ‘pure’ function w/ parallel evaluation & memo combinators -------------------------------------+------------------------------------- Reporter: pacak | Owner: bgamari Type: bug | Status: new Priority: highest | Milestone: 8.2.1 Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): So with `-A8k` the incorrect behavior seems to disappear entirely, but with the expected degradation in performance. However, it's hard to rule out that this is merely due a change in timings. However, I've also confirmed that we are indeed entering `unsafeInsertWith` multiple times on the same `HashMap`. I've instrumented `unsafeInsertWith` to record when it is entered (within the context of a particular `fromListWith` call) and found that indeed we do see multiple threads entering concurrently. Looking at the stacks of the threads involved in the multiple entry, I see some highly suspicious behavior. Namely, the top twenty or so frames are nearly identical. For instance, we have {{{#!diff --- +++ @@ -1,7 +1,11 @@ -thread 17 (entered first) +thread 16 (entered second) ----------------------------------- 0: RET_SMALL + return = 0x434298 (symbol and line for ./Data/HashMap/Strict.hs, line 93) + field 0: Ptr 0x434298 + field 1: Word 283476377554 +1: RET_SMALL return = 0x439338 (symbol and line for ./Data/HashMap/Strict.hs, line 166) field 0: Ptr 0x439338 field 1: Ptr 0x420072cea0 @@ -11,36 +15,36 @@ field 5: Ptr 0x42008230b0 field 6: Ptr 0x420082312d field 7: Word 283476377554 -1: RET_SMALL +2: RET_SMALL return = 0x439498 (symbol and line for ./Data/HashMap/Strict.hs, line 160) -2: UPDATE_FRAME(0x4200810610: BLACKHOLE(0x420046661a: constr)) -3: RET_SMALL +3: UPDATE_FRAME(0x4200810610: BLACKHOLE(0x420046661a: constr)) +4: RET_SMALL return = 0x44c790 (symbol and line for ./Data/HashMap/Base.hs, line 122) field 0: Ptr 0x44c790 field 1: Word 283476373666 -4: UPDATE_FRAME(0x4200810678: BLACKHOLE(0x42004694fa: constr)) -5: RET_SMALL +5: UPDATE_FRAME(0x4200810678: BLACKHOLE(0x42004694fa: constr)) +6: RET_SMALL return = 0x471b98 (symbol and line for libraries/base/GHC/Base.hs, line 946) field 0: Word 4660120 -6: UPDATE_FRAME(0x42008106b0: BLACKHOLE(0x4200469552: constr)) -7: RET_SMALL +7: UPDATE_FRAME(0x42008106b0: BLACKHOLE(0x4200469552: constr)) +8: RET_SMALL return = 0x4af310 (symbol and line for libraries/base/GHC/List.hs, line 187) field 0: Word 4911888 field 1: Word 283476373528 field 2: Ptr 0x420082305a -8: RET_SMALL +9: RET_SMALL return = 0x40abb8 (symbol and line for src/Solver.hs, line 41) field 0: Word 4238264 field 1: Ptr 0x4200822f78 field 2: Word 283476373392 field 3: Ptr 0x4200822ee0 field 4: Ptr 0x4200822f00 -9: UPDATE_FRAME(0x42008106e0: BLACKHOLE(0x42004414b0: THUNK)) -10: RET_SMALL +10: UPDATE_FRAME(0x42008106e0: BLACKHOLE(0x42004414b0: THUNK)) +11: RET_SMALL return = 0x471d10 (symbol and line for libraries/base/GHC/Base.hs, line 860) field 0: Word 4660496 -11: UPDATE_FRAME(0x4200724cf8: THUNK) -12: RET_SMALL +12: UPDATE_FRAME(0x4200724cf8: THUNK) +13: RET_SMALL return = 0x4392c8 (symbol and line for ./Data/HashMap/Strict.hs, line 164) field 0: Word 4428488 field 1: Word 283469122208 @@ -48,86 +52,85 @@ field 3: Ptr 0x7ec538 field 4: Ptr 0x4200138a90 field 5: Ptr 0x4200138b0d - field 6: Ptr 0x420007ae22 -13: RET_SMALL + field 6: Ptr 0x4200724e9a +14: RET_SMALL return = 0x439498 (symbol and line for ./Data/HashMap/Strict.hs, line 160) -14: UPDATE_FRAME(0x420010bb98: AP_STACK(size=9, fun=BLACKHOLE(0x4200724062: constr), payload=0x420010bbb8)) -15: RET_SMALL +15: UPDATE_FRAME(0x420010bb98: AP_STACK(size=9, fun=BLACKHOLE(0x4200724062: constr), payload=0x420010bbb8)) +16: RET_SMALL return = 0x44c790 (symbol and line for ./Data/HashMap/Base.hs, line 122) field 0: Ptr 0x44c790 field 1: Word 283469122178 -16: UPDATE_FRAME(0x420010bc00: AP_STACK(size=3, fun=AP_STACK(size=9, fun=BLACKHOLE(0x4200724062: constr), payload=0x420010bbb8), payload=0x420010bc20)) -17: RET_SMALL +17: UPDATE_FRAME(0x420010bc00: AP_STACK(size=3, fun=AP_STACK(size=9, fun=BLACKHOLE(0x4200724062: constr), payload=0x420010bbb8), payload=0x420010bc20)) +18: RET_SMALL return = 0x471b98 (symbol and line for libraries/base/GHC/Base.hs, line 946) field 0: Word 4660120 -18: UPDATE_FRAME(0x420010bc38: AP_STACK(size=2, fun=AP_STACK(size=3, fun=AP_STACK(size=9, fun=BLACKHOLE(0x4200724062: constr), payload=0x420010bbb8), payload=0x420010bc20), payload=0x420010bc58)) -19: RET_SMALL +19: UPDATE_FRAME(0x420010bc38: AP_STACK(size=2, fun=AP_STACK(size=3, fun=AP_STACK(size=9, fun=BLACKHOLE(0x4200724062: constr), payload=0x420010bbb8), payload=0x420010bc20), payload=0x420010bc58)) +20: RET_SMALL return = 0x4af310 (symbol and line for libraries/base/GHC/List.hs, line 187) field 0: Word 4911888 field 1: Word 283469122040 field 2: Ptr 0x4200138a3a -20: RET_SMALL +21: RET_SMALL return = 0x40abb8 (symbol and line for src/Solver.hs, line 41) field 0: Word 4238264 field 1: Ptr 0x4200138968 field 2: Word 283469121920 field 3: Ptr 0x42001388d0 field 4: Ptr 0x42001388f0 -21: UPDATE_FRAME(0x420010bc68: AP_STACK(size=10, fun=AP_STACK(size=2, fun=AP_STACK(size=3, fun=AP_STACK(size=9, fun=BLACKHOLE(0x4200724062: constr), payload=0x420010bbb8), payload=0x420010bc20), payload=0x420010bc58), payload=0x420010bc88)) -22: UPDATE_FRAME(0x4200056810: BLACKHOLE(0x420000bc50: TSO)) -23: RET_SMALL +22: UPDATE_FRAME(0x420010bc68: AP_STACK(size=10, fun=AP_STACK(size=2, fun=AP_STACK(size=3, fun=AP_STACK(size=9, fun=BLACKHOLE(0x4200724062: constr), payload=0x420010bbb8), payload=0x420010bc20), payload=0x420010bc58), payload=0x420010bc88)) +23: UPDATE_FRAME(0x420086c660: BLACKHOLE(0x420086f000: TSO)) +24: RET_SMALL return = 0x471d38 (symbol and line for libraries/base/GHC/Base.hs, line 859) field 0: Ptr 0x471d38 - field 1: Word 283468195841 -24: UPDATE_FRAME(0x4200056560: BLACKHOLE(0x420000bc50: TSO)) -25: RET_SMALL + field 1: Word 283476674129 +25: UPDATE_FRAME(0x420086c3b0: BLACKHOLE(0x420086f000: TSO)) +26: RET_SMALL return = 0x4392c8 (symbol and line for ./Data/HashMap/Strict.hs, line 164) field 0: Word 4428488 - field 1: Word 283468195696 - field 2: Word 283468195296 + field 1: Word 283476673984 + field 2: Word 283476673584 field 3: Ptr 0x7e60c8 - field 4: Ptr 0x4200056760 - field 5: Ptr 0x42000567dd + field 4: Ptr 0x420086c5b0 + field 5: Ptr 0x420086c62d field 6: Ptr 0x7ee011 -26: RET_SMALL +27: RET_SMALL return = 0x439498 (symbol and line for ./Data/HashMap/Strict.hs, line 160) -27: UPDATE_FRAME(0x4200056718: BLACKHOLE(0x420000bc50: TSO)) -28: RET_SMALL +28: UPDATE_FRAME(0x420086c568: BLACKHOLE(0x420086f000: TSO)) +29: RET_SMALL return = 0x44c790 (symbol and line for ./Data/HashMap/Base.hs, line 122) field 0: Ptr 0x44c790 - field 1: Word 283468195666 -29: UPDATE_FRAME(0x4200056650: BLACKHOLE(0x420000bc50: TSO)) -30: RET_SMALL + field 1: Word 283476673954 +30: UPDATE_FRAME(0x420086c4a0: BLACKHOLE(0x420086f000: TSO)) +31: RET_SMALL return = 0x471b98 (symbol and line for libraries/base/GHC/Base.hs, line 946) field 0: Word 4660120 -31: UPDATE_FRAME(0x4200056688: BLACKHOLE(0x420000bc50: TSO)) -32: RET_SMALL +32: UPDATE_FRAME(0x420086c4d8: BLACKHOLE(0x420086f000: TSO)) +33: RET_SMALL return = 0x4af310 (symbol and line for libraries/base/GHC/List.hs, line 187) field 0: Word 4911888 - field 1: Word 283468195528 - field 2: Ptr 0x420005670a -33: RET_SMALL + field 1: Word 283476673816 + field 2: Ptr 0x420086c55a +34: RET_SMALL return = 0x40abb8 (symbol and line for src/Solver.hs, line 41) field 0: Word 4238264 - field 1: Ptr 0x4200056638 - field 2: Word 283468195408 - field 3: Ptr 0x42000565a0 - field 4: Ptr 0x42000565c0 -34: UPDATE_FRAME(0x4200056528: BLACKHOLE(0x420000bc50: TSO)) -35: RET_SMALL + field 1: Ptr 0x420086c488 + field 2: Word 283476673696 + field 3: Ptr 0x420086c3f0 + field 4: Ptr 0x420086c410 +35: UPDATE_FRAME(0x420086c378: BLACKHOLE(0x420086f000: TSO)) +36: RET_SMALL return = 0x471d38 (symbol and line for libraries/base/GHC/Base.hs, line 859) field 0: Ptr 0x471d38 - field 1: Word 283468195081 -36: UPDATE_FRAME(0x4200056258: BLACKHOLE(0x420000bc50: TSO)) -37: RET_SMALL + field 1: Word 283476673369 +37: UPDATE_FRAME(0x420086c0a8: BLACKHOLE(0x420086f000: TSO)) +38: RET_SMALL return = 0x4392c8 (symbol and line for ./Data/HashMap/Strict.hs, line 164) field 0: Word 4428488 - field 1: Word 283468194936 - field 2: Word 283468194536 + field 1: Word 283476673224 + field 2: Word 283476672824 field 3: Ptr 0x7ebb39 - field 4: Ptr 0x4200056468 - field 5: Ptr 0x42000564e5 + field 4: Ptr 0x420086c2b8 + field 5: Ptr 0x420086c335 field 6: Ptr 0x7ee011 -38: RET_SMALL +39: RET_SMALL return = 0x439498 (symbol and line for ./Data/HashMap/Strict.hs, line 160) -39: UPDATE_FRAME(0x4200056420: BLACKHOLE(0x420000bc50: TSO)) }}} Here we see that the threads' stacks differ by only a single word (save frame 0, which is merely an artifact of my instrumentation) in the first 21 frames. Intriguingly, they begin to differ after frame 21/22, which is an update frame updating an `AP_STACK`. Strangely, the only way that we can end up with such a closure is via the `raiseAsync` machinery or via the bytecode interpreter. There's clearly still more digging to do. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jun 7 15:32:23 2017 From: ghc-devs at haskell.org (GHC) Date: Wed, 07 Jun 2017 15:32:23 -0000 Subject: [GHC] #13652: Add integer division to GHC.TypeLits In-Reply-To: <048.b9612e3f8a829526a91743f198cf1ed8@haskell.org> References: <048.b9612e3f8a829526a91743f198cf1ed8@haskell.org> Message-ID: <063.9726b9331f8aef07245e37bbda71f16f@haskell.org> #13652: Add integer division to GHC.TypeLits -------------------------------------+------------------------------------- Reporter: vagarenko | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: Component: Core Libraries | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * component: Compiler => Core Libraries Comment: Libraries mailing list discussion: https://mail.haskell.org/pipermail/libraries/2017-June/028057.html -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jun 7 15:35:32 2017 From: ghc-devs at haskell.org (GHC) Date: Wed, 07 Jun 2017 15:35:32 -0000 Subject: [GHC] #13750: GHC produces incorrect coercions in hairy code In-Reply-To: <045.2957c281e52a0617c4b44226d50f7bbc@haskell.org> References: <045.2957c281e52a0617c4b44226d50f7bbc@haskell.org> Message-ID: <060.736234c216f431a0aeef939afd892a8d@haskell.org> #13750: GHC produces incorrect coercions in hairy code -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: (none) Type: bug | Status: new Priority: highest | Milestone: 8.2.2 Component: Compiler | Version: 8.2.1-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Runtime crash | Test Case: Blocked By: | Blocking: Related Tickets: #13429 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by kosmikus): This is good news. Thanks a lot. I will test my original program as soon as I have a GHC with this patch available. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jun 7 15:36:36 2017 From: ghc-devs at haskell.org (GHC) Date: Wed, 07 Jun 2017 15:36:36 -0000 Subject: [GHC] #13373: Handle long file paths on Windows In-Reply-To: <045.872d530b642536033e5f70fd0cb14d01@haskell.org> References: <045.872d530b642536033e5f70fd0cb14d01@haskell.org> Message-ID: <060.ba3954cd24f95528bf7580027541f717@haskell.org> #13373: Handle long file paths on Windows -------------------------------------+------------------------------------- Reporter: ezyang | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: Component: libraries/base | Version: 8.1 Resolution: | Keywords: Operating System: Windows | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by joeyhess): Due to https://ghc.haskell.org/trac/ghc/ticket/13796 it's hard to make ghc embed a custom manifest file to enable long filename support. However, use -fno-embed-manifest and when running foo.exe, windows will read a side-by- side foo.exe.manifest file. I tested this with a foo.hs containing main = writeFile (take 300 (cycle "a")) "hello" Despite the manifest enabling long file support, on Windows 10 that fails with "openFile: does not exist". Seems that long file support includes CreateFileW, but ghc's openFile uses _wsopen, which is not included in the long file support. This makes the manifest approach only useful for some subset of programs. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jun 7 15:36:37 2017 From: ghc-devs at haskell.org (GHC) Date: Wed, 07 Jun 2017 15:36:37 -0000 Subject: =?utf-8?b?UmU6IFtHSENdICMxMzYxNTogTm9uZGV0ZXJtaW5pc20gaW4g4oCY?= =?utf-8?q?pure=E2=80=99_function_w/_parallel_evaluation_=26_memo?= =?utf-8?q?_combinators?= In-Reply-To: <044.57733831351687fff6258688df1f42f7@haskell.org> References: <044.57733831351687fff6258688df1f42f7@haskell.org> Message-ID: <059.b05887ed01b1aa35fd13101bf5077703@haskell.org> #13615: Nondeterminism in ‘pure’ function w/ parallel evaluation & memo combinators -------------------------------------+------------------------------------- Reporter: pacak | Owner: bgamari Type: bug | Status: new Priority: highest | Milestone: 8.2.1 Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): Ahh, of course; the `AP_STACK` is presumably being produced by `raiseAsync` while suspending a thread in preparation for GC. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jun 7 16:33:34 2017 From: ghc-devs at haskell.org (GHC) Date: Wed, 07 Jun 2017 16:33:34 -0000 Subject: =?utf-8?b?UmU6IFtHSENdICMxMzYxNTogTm9uZGV0ZXJtaW5pc20gaW4g4oCY?= =?utf-8?q?pure=E2=80=99_function_w/_parallel_evaluation_=26_memo?= =?utf-8?q?_combinators?= In-Reply-To: <044.57733831351687fff6258688df1f42f7@haskell.org> References: <044.57733831351687fff6258688df1f42f7@haskell.org> Message-ID: <059.b259046b88f381db9e902df773469238@haskell.org> #13615: Nondeterminism in ‘pure’ function w/ parallel evaluation & memo combinators -------------------------------------+------------------------------------- Reporter: pacak | Owner: bgamari Type: bug | Status: new Priority: highest | Milestone: 8.2.1 Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): One interesting observation is that the issue persists even if the list passed to `fromListWith` is fully forced; that is, {{{#!hs let xs' = deepseq xs `seq` HM.toList (HM.fromListWith (+) xs) }}} instead of {{{#!hs let xs' = HM.toList (HM.fromListWith (+) xs) }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jun 7 16:36:16 2017 From: ghc-devs at haskell.org (GHC) Date: Wed, 07 Jun 2017 16:36:16 -0000 Subject: [GHC] #13798: Invalid transformation in simplOptExpr Message-ID: <046.b24b0491e12a3382c6b573e031c76ef8@haskell.org> #13798: Invalid transformation in simplOptExpr -------------------------------------+------------------------------------- Reporter: simonpj | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- Prior to [https://git.haskell.org/ghc.git/commitdiff/1722fa106e10e63160bb2322e2ccb830fd5b9ab3 this commit], `CoreOpt.simple_opt_expr` transforms {{{ case e of (b :: t1 ~# t2) DEFAULT -> rhs ==> rhs }}} That was plain wrong when `e` diverges, or calls `error`. Hence the commit. But the commit does this {{{ case Coercible_sc e of (b :: t1 ~# t2) DEFAULT -> rhs ==> rhs }}} narrowing the scope of the transformation to when the scrutinee is application of the Coercible superclass selector {{{ Coercible_sc :: Coercible a b -> (a ~R# b) }}} Here's the code from `CoreOpt`: {{{ | isDeadBinder b , [(DEFAULT, _, rhs)] <- as , isCoercionType (varType b) , (Var fun, _args) <- collectArgs e , fun `hasKey` coercibleSCSelIdKey -- without this last check, we get #11230 = go rhs }}} But that's bizarrely ad-hoc. And, worse, it is flat-out wrong... what if `e` diverges? It's not actually hurting anyone right now, but what we should really do is use `exprOkForSpeculation`; and teach `exprOkForSpeculation` how to deal with class-op selectors. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jun 7 16:39:20 2017 From: ghc-devs at haskell.org (GHC) Date: Wed, 07 Jun 2017 16:39:20 -0000 Subject: [GHC] #12545: Compilation time/space regression in GHC 8.0/8.1 (search in type-level lists and -O) In-Reply-To: <057.9aecaec89b7fd255565e55bac0801cc6@haskell.org> References: <057.9aecaec89b7fd255565e55bac0801cc6@haskell.org> Message-ID: <072.fb788979aa8d6826c737f3858d16c3b2@haskell.org> #12545: Compilation time/space regression in GHC 8.0/8.1 (search in type-level lists and -O) -------------------------------------+------------------------------------- Reporter: | Owner: (none) mikhail.vorozhtsov | Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Inlining Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): See [https://mail.haskell.org/pipermail/ghc-devs/2017-May/014277.html this ghc-devs thread], and [https://mail.haskell.org/pipermail/ghc- devs/2017-June/014278.html this one]. There seem to be several issues: * Why does the small change identified by Ryan have such a huge effect? We need insight. * The change that Richard made to `CoreOpt.simple_opt_expr` actually fixed an outright bug. But it's ''still'' wrong now. See Trac #13798. * The fuss that is caused by this `map/coerce` rule is out of all proportion to its importance. We should think of a better way. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jun 7 16:45:43 2017 From: ghc-devs at haskell.org (GHC) Date: Wed, 07 Jun 2017 16:45:43 -0000 Subject: [GHC] #12545: Compilation time/space regression in GHC 8.0/8.1 (search in type-level lists and -O) In-Reply-To: <057.9aecaec89b7fd255565e55bac0801cc6@haskell.org> References: <057.9aecaec89b7fd255565e55bac0801cc6@haskell.org> Message-ID: <072.28599086be1bdbf58e74520f61efb6c0@haskell.org> #12545: Compilation time/space regression in GHC 8.0/8.1 (search in type-level lists and -O) -------------------------------------+------------------------------------- Reporter: | Owner: (none) mikhail.vorozhtsov | Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Inlining Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): Incidentally, HEAD is much much better: {{{ 7.10 19.2G allocated by GHC 50 seconds HEAD 7.1G allocated by GHC 30 seconds }}} I gave up waiting for 8.0. So apparently the original problem has gone away, although I'd quite like to know how! -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jun 7 17:09:18 2017 From: ghc-devs at haskell.org (GHC) Date: Wed, 07 Jun 2017 17:09:18 -0000 Subject: =?utf-8?b?UmU6IFtHSENdICMxMzYxNTogTm9uZGV0ZXJtaW5pc20gaW4g4oCY?= =?utf-8?q?pure=E2=80=99_function_w/_parallel_evaluation_=26_memo?= =?utf-8?q?_combinators?= In-Reply-To: <044.57733831351687fff6258688df1f42f7@haskell.org> References: <044.57733831351687fff6258688df1f42f7@haskell.org> Message-ID: <059.e9075886b642eb51fee0b867190a4dee@haskell.org> #13615: Nondeterminism in ‘pure’ function w/ parallel evaluation & memo combinators -------------------------------------+------------------------------------- Reporter: pacak | Owner: bgamari Type: bug | Status: new Priority: highest | Milestone: 8.2.1 Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): Alright, I think I have a theory for how we end up getting multiple entries despite having no thunk allocation inside `fromListWith`: 1. Thread A enters a `fromListWith` closure and begins folding over the insertions 2. At some point during this fold we need to garbage collect; the garbage collector constructs an `AP_STACK` closure capturing the state of Thread A, including the partially-finished `fromListWith` computation 3. Garbage collection commences and finishes, evaluation resumes 4. At some point Thread A is resumed, picking up the previously suspended `fromListWith` computation; we are blackholing lazily so no update to the closure is made 5. At some later Thread B tries to force the same `fromListWith` computation; finding that it's not blackholed it enters 6. We now have two mutator threads performing evaluation on the same, effectful computation with shared, mutable state. Does this sound plausible? The only bit that I'm a bit hazy on is point (5). That is, how is it that Thread B is able to enter the suspended computation given that (if I understand correctly) Thread A won't update the original `fromListWith` until finishes its evaluation and pops its associated update frame. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jun 7 17:26:10 2017 From: ghc-devs at haskell.org (GHC) Date: Wed, 07 Jun 2017 17:26:10 -0000 Subject: [GHC] #13608: Expose the type of quasiquotes In-Reply-To: <056.25d1d92a9495f18e85d0ecacba264382@haskell.org> References: <056.25d1d92a9495f18e85d0ecacba264382@haskell.org> Message-ID: <071.f9b84cb215fa7b65773615a9d3f26fb6@haskell.org> #13608: Expose the type of quasiquotes -------------------------------------+------------------------------------- Reporter: | Owner: facundo.dominguez | facundo.dominguez Type: bug | Status: patch Priority: normal | Milestone: Component: Template Haskell | Version: 8.0.1 Resolution: | Keywords: QuasiQuotes Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: 12778 | Differential Rev(s): Phab:D3610 Wiki Page: | -------------------------------------+------------------------------------- Comment (by facundo.dominguez): > I don't understand the nested-splice issue. Suppose we have solved this problem for top-level splices, `[java| ... |]` gets the types it needs. Then one day someone tries `[| ... [java| ... |] ... |]`, and finds that it fails because the java quasiquoter gets the type of the top-level splice instead of its own type which occurs nested in the outer brackets. The solution discussed in ticket:12778#comment:11 is more attractive in this regard. It says: design any feature to work with outer splices. Presto! It will also work with nested splices because they are treated the same. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jun 7 17:58:57 2017 From: ghc-devs at haskell.org (GHC) Date: Wed, 07 Jun 2017 17:58:57 -0000 Subject: [GHC] #13796: hard to embed custom manifest on windows In-Reply-To: <047.a85c2b7fd2ccf64d7a50d2285d24d244@haskell.org> References: <047.a85c2b7fd2ccf64d7a50d2285d24d244@haskell.org> Message-ID: <062.94fb3e91084853c6e213d4459b1a8b86@haskell.org> #13796: hard to embed custom manifest on windows ---------------------------------+---------------------------------------- Reporter: joeyhess | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.2 Resolution: | Keywords: Operating System: Windows | Architecture: Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | ---------------------------------+---------------------------------------- Comment (by garethr): Would it be possible to opt in to long filenames by default on Windows 10? Is there any part of ghc or a library that assumes paths have a maximum of 260 characters? The relevant Microsoft documentation is here: https://msdn.microsoft.com/en- gb/library/windows/desktop/aa365247(v=vs.85).aspx#maxpath Tip Starting in Windows 10, version 1607, MAX_PATH limitations have been removed from common Win32 file and directory functions. However, you must opt-in to the new behavior. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jun 7 18:32:08 2017 From: ghc-devs at haskell.org (GHC) Date: Wed, 07 Jun 2017 18:32:08 -0000 Subject: [GHC] #13756: Typo in user guide suggests that there's an -O* option In-Reply-To: <042.6a3b1c429314348df414591c312b566f@haskell.org> References: <042.6a3b1c429314348df414591c312b566f@haskell.org> Message-ID: <057.0e1dd1be38e10711cf01d3fc6eb90f7c@haskell.org> #13756: Typo in user guide suggests that there's an -O* option -------------------------------------+------------------------------------- Reporter: nh2 | Owner: SantiM Type: bug | Status: new Priority: normal | Milestone: 8.2.1 Component: Documentation | Version: 8.0.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): D3631 Wiki Page: | -------------------------------------+------------------------------------- Changes (by SantiM): * owner: (none) => SantiM * differential: => D3631 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jun 7 18:33:34 2017 From: ghc-devs at haskell.org (GHC) Date: Wed, 07 Jun 2017 18:33:34 -0000 Subject: [GHC] #13756: Typo in user guide suggests that there's an -O* option In-Reply-To: <042.6a3b1c429314348df414591c312b566f@haskell.org> References: <042.6a3b1c429314348df414591c312b566f@haskell.org> Message-ID: <057.f3a8f4bd8334c5c35870e38128cb5ec6@haskell.org> #13756: Typo in user guide suggests that there's an -O* option -------------------------------------+------------------------------------- Reporter: nh2 | Owner: SantiM Type: bug | Status: new Priority: normal | Milestone: 8.2.1 Component: Documentation | Version: 8.0.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3631 Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * differential: D3631 => Phab:D3631 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jun 7 18:54:13 2017 From: ghc-devs at haskell.org (GHC) Date: Wed, 07 Jun 2017 18:54:13 -0000 Subject: [GHC] #11501: Building nofib/fibon returns permission denied In-Reply-To: <042.7732253ef90810c7acc41907aecb19ff@haskell.org> References: <042.7732253ef90810c7acc41907aecb19ff@haskell.org> Message-ID: <057.311d87987bcde56b839571d58093e11d@haskell.org> #11501: Building nofib/fibon returns permission denied -------------------------------------+------------------------------------- Reporter: rem | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: NoFib benchmark | Version: 7.10.3 suite | Resolution: | Keywords: Operating System: Linux | Architecture: x86_64 | (amd64) Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Michal Terepeta ): In [changeset:"50812b141f1a6c372c85cceb3541e9c1c7bab926/nofib" 50812b1/nofib]: {{{ #!CommitTicketReference repository="nofib" revision="50812b141f1a6c372c85cceb3541e9c1c7bab926" Remove fibon Summary: It doesn't compile, nobody is running it and upstream seems to have abandoned it too. IMHO, at this point we should simply remove it and focus on improving the benchmarks that do work & adding new ones. See also the discussion in #11501 Signed-off-by: Michal Terepeta Test Plan: compile & run nofib Reviewers: bgamari Subscribers: }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jun 7 19:03:10 2017 From: ghc-devs at haskell.org (GHC) Date: Wed, 07 Jun 2017 19:03:10 -0000 Subject: [GHC] #12545: Compilation time/space regression in GHC 8.0/8.1 (search in type-level lists and -O) In-Reply-To: <057.9aecaec89b7fd255565e55bac0801cc6@haskell.org> References: <057.9aecaec89b7fd255565e55bac0801cc6@haskell.org> Message-ID: <072.a5359cd00142dc8e9b7a14aad5e6c348@haskell.org> #12545: Compilation time/space regression in GHC 8.0/8.1 (search in type-level lists and -O) -------------------------------------+------------------------------------- Reporter: | Owner: (none) mikhail.vorozhtsov | Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Inlining Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): Well hot dang. It turns out that commit 2b74bd9d8b4c6b20f3e8d9ada12e7db645cc3c19 (Stop the specialiser generating loopy code) is once again responsible for fixing the problem! {{{ Commit 92a4f908f2599150bec0530d688997f03780646e (Spelling typos) <> real 0m59.150s user 0m59.020s sys 0m0.224s Commit 2b74bd9d8b4c6b20f3e8d9ada12e7db645cc3c19 (Stop the specialiser generating loopy code) <> real 0m4.549s user 0m4.440s sys 0m0.096s }}} For reference, the time for GHC 7.10.3 was: {{{ <> real 0m13.477s user 0m13.128s sys 0m0.104s }}} So now it's even //better// than it used to be! That's pretty cool. I don't have any particular insight as to why that commit made things so much better, but sure enough, `TypeList.hs` contains some classes with significant superclasses: {{{#!hs class (FindElem 'HeadElem a l ~ 'Elem p) => ElemAt p (a :: k) (l :: [k]) where elemWitness :: Proxy a -> Proxy l -> ElemWitness p a l class IsElem t (ElemsOf a) => ElemOf a t where }}} So it's entirely possible that their corresponding dictionaries are just getting optimized better. It would be great to have someone verify this at the Core level. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jun 7 20:20:27 2017 From: ghc-devs at haskell.org (GHC) Date: Wed, 07 Jun 2017 20:20:27 -0000 Subject: [GHC] #13798: Invalid transformation in simplOptExpr In-Reply-To: <046.b24b0491e12a3382c6b573e031c76ef8@haskell.org> References: <046.b24b0491e12a3382c6b573e031c76ef8@haskell.org> Message-ID: <061.35415bb70659a986fe07a4238dff9d9d@haskell.org> #13798: Invalid transformation in simplOptExpr -------------------------------------+------------------------------------- Reporter: simonpj | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by goldfire): A related question, while your attention is on this code, is why the case- of-known-constructor optimization immediately above this code doesn't detect the `Coercible_sc` selector applied to `MkCoercible`. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jun 7 20:25:33 2017 From: ghc-devs at haskell.org (GHC) Date: Wed, 07 Jun 2017 20:25:33 -0000 Subject: [GHC] #13796: hard to embed custom manifest on windows In-Reply-To: <047.a85c2b7fd2ccf64d7a50d2285d24d244@haskell.org> References: <047.a85c2b7fd2ccf64d7a50d2285d24d244@haskell.org> Message-ID: <062.ee0ad443a664d725966bdf4d3cd3da97@haskell.org> #13796: hard to embed custom manifest on windows ---------------------------------+---------------------------------------- Reporter: joeyhess | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.2 Resolution: | Keywords: Operating System: Windows | Architecture: Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | ---------------------------------+---------------------------------------- Comment (by joeyhess): See https://ghc.haskell.org/trac/ghc/ticket/13373 for the long paths on windows issue. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jun 7 20:30:04 2017 From: ghc-devs at haskell.org (GHC) Date: Wed, 07 Jun 2017 20:30:04 -0000 Subject: [GHC] #12390: List rules for `Coercible` instances In-Reply-To: <051.b98e23ec385e9c48fab8abae2b183162@haskell.org> References: <051.b98e23ec385e9c48fab8abae2b183162@haskell.org> Message-ID: <066.c032982816651c2cd181c32267352110@haskell.org> #12390: List rules for `Coercible` instances -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by tellah): Newcomer here who has been poking around this a bit. From my initial impressions of the `:info` code, it would appear that the only place such an info string could be stored is in the TyThing. This is because the input string is converted String -> Name -> TyThing, and then the TyThing is converted to an IfaceDecl for printing. So then the question is: where does the suggested info string come from? I have some basic code that can store arbitrary text for `:info` but I am not sure what the front end for this should look like. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jun 7 20:33:41 2017 From: ghc-devs at haskell.org (GHC) Date: Wed, 07 Jun 2017 20:33:41 -0000 Subject: [GHC] #12390: List rules for `Coercible` instances In-Reply-To: <051.b98e23ec385e9c48fab8abae2b183162@haskell.org> References: <051.b98e23ec385e9c48fab8abae2b183162@haskell.org> Message-ID: <066.140e68ad1c6a15086d4ac45f1497d5e2@haskell.org> #12390: List rules for `Coercible` instances -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Iceland_jack): > Note that we stopped calling Coercible a class; as '''it is not a class'''. If it's all the same I would like `:info` to mention that -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jun 7 22:27:37 2017 From: ghc-devs at haskell.org (GHC) Date: Wed, 07 Jun 2017 22:27:37 -0000 Subject: [GHC] #10843: Allow do blocks without dollar signs as arguments In-Reply-To: <049.979a39a09d7a881598f53a6a6ce9bbe3@haskell.org> References: <049.979a39a09d7a881598f53a6a6ce9bbe3@haskell.org> Message-ID: <064.c9a4c405b3f3ea4541e4e19c835ced22@haskell.org> #10843: Allow do blocks without dollar signs as arguments -------------------------------------+------------------------------------- Reporter: agibiansky | Owner: agibiansky Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.2 (Parser) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #11706 | Differential Rev(s): Phab:D1219 Wiki Page: | -------------------------------------+------------------------------------- Comment (by Iceland_jack): [https://gist.github.com/Icelandjack/5bdaea3692891a1ca3fbe6b7bbfd4cef gist] with examples -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jun 7 23:00:15 2017 From: ghc-devs at haskell.org (GHC) Date: Wed, 07 Jun 2017 23:00:15 -0000 Subject: [GHC] #13799: -ddump-splices prints out declarations in the wrong order Message-ID: <050.f45d5f324cc6583163c58bb2b6f6629d@haskell.org> #13799: -ddump-splices prints out declarations in the wrong order -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Template | Version: 8.0.1 Haskell | Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: Debugging Unknown/Multiple | information is incorrect Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- {{{#!hs {-# LANGUAGE StandaloneDeriving #-} {-# LANGUAGE TemplateHaskell #-} {-# OPTIONS_GHC -ddump-splices #-} module Bug where $([d| data A = A data B = B |]) $([d| deriving instance Eq A deriving instance Eq B |]) }}} {{{ GHCi, version 8.0.2: http://www.haskell.org/ghc/ :? for help Loaded GHCi configuration from /home/rgscott/.ghci [1 of 1] Compiling Bug ( Bug.hs, interpreted ) Bug.hs:(6,3)-(8,6): Splicing declarations [d| data A_a13D = A_a13E data B_a13B = B_a13C |] ======> data A_a3IA = A_a3IB data B_a3IC = B_a3ID Bug.hs:(10,3)-(12,6): Splicing declarations [d| deriving instance Eq B deriving instance Eq A |] ======> deriving instance Eq A deriving instance Eq B }}} Notice that it printed {{{#!hs [d| deriving instance Eq B deriving instance Eq A |] }}} instead of {{{#!hs [d| deriving instance Eq A deriving instance Eq B |] }}} which is what I originally wrote. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jun 7 23:26:18 2017 From: ghc-devs at haskell.org (GHC) Date: Wed, 07 Jun 2017 23:26:18 -0000 Subject: [GHC] #13795: :kind! is not expanding type synonyms anymore In-Reply-To: <045.9bd0a404a46fb5b0930c49818b8cb45d@haskell.org> References: <045.9bd0a404a46fb5b0930c49818b8cb45d@haskell.org> Message-ID: <060.0036b9b4757f08b4defdb8b772246da4@haskell.org> #13795: :kind! is not expanding type synonyms anymore -------------------------------------+------------------------------------- Reporter: Hjulle | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: GHCi | Version: 8.0.2 Resolution: | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): Replying to [comment:2 simonpj]: > Did `:kind!` ever expand synonyms? > > The user manual claims that it does, but I can see no evidence that it ever did. It did in GHC 7.8.4: {{{ 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. λ> type A = () λ> :kind! A A :: * = () }}} But not in GHC 7.10.3: {{{ GHCi, version 7.10.3: http://www.haskell.org/ghc/ :? for help λ> type A = Bool λ> :kind! A A :: * = A }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jun 7 23:26:55 2017 From: ghc-devs at haskell.org (GHC) Date: Wed, 07 Jun 2017 23:26:55 -0000 Subject: [GHC] #13429: Optimizer produces Core with an infinite <> In-Reply-To: <045.cf5ba15167896826f7f0c0a59d69b609@haskell.org> References: <045.cf5ba15167896826f7f0c0a59d69b609@haskell.org> Message-ID: <060.d4cd7510df146c0ef6cb539c73c04ce2@haskell.org> #13429: Optimizer produces Core with an infinite <> -------------------------------------+------------------------------------- Reporter: lehins | Owner: simonpj Type: bug | Status: merge Priority: highest | Milestone: 8.2.1 Component: Compiler | Version: 8.0.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Runtime crash | Test Case: | simplCore/should_run/T13429, | T13429_2 Blocked By: | Blocking: Related Tickets: #13750 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by nh2): I've backported the above fix to GHC 8.0.2 and created bindist for Linux: https://github.com/nh2/ghc/releases/tag/ghc-8.0.2-bugfix-12545-backport-2017-06-08 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jun 7 23:27:34 2017 From: ghc-devs at haskell.org (GHC) Date: Wed, 07 Jun 2017 23:27:34 -0000 Subject: [GHC] #13429: Optimizer produces Core with an infinite <> In-Reply-To: <045.cf5ba15167896826f7f0c0a59d69b609@haskell.org> References: <045.cf5ba15167896826f7f0c0a59d69b609@haskell.org> Message-ID: <060.f2011cdcda0b696ae1417e90e95c3766@haskell.org> #13429: Optimizer produces Core with an infinite <> -------------------------------------+------------------------------------- Reporter: lehins | Owner: simonpj Type: bug | Status: merge Priority: highest | Milestone: 8.2.1 Component: Compiler | Version: 8.0.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Runtime crash | Test Case: | simplCore/should_run/T13429, | T13429_2 Blocked By: | Blocking: Related Tickets: #13750, #12545 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by nh2): * cc: nh2 (added) * related: #13750 => #13750, #12545 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jun 7 23:28:58 2017 From: ghc-devs at haskell.org (GHC) Date: Wed, 07 Jun 2017 23:28:58 -0000 Subject: [GHC] #12545: Compilation time/space regression in GHC 8.0/8.1 (search in type-level lists and -O) In-Reply-To: <057.9aecaec89b7fd255565e55bac0801cc6@haskell.org> References: <057.9aecaec89b7fd255565e55bac0801cc6@haskell.org> Message-ID: <072.3c6c2be84694c4e126161b27354986ee@haskell.org> #12545: Compilation time/space regression in GHC 8.0/8.1 (search in type-level lists and -O) -------------------------------------+------------------------------------- Reporter: | Owner: (none) mikhail.vorozhtsov | Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Inlining Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by nh2): I've backported the above mentioned fix to GHC 8.0.2 and created bindist for Linux: https://github.com/nh2/ghc/releases/tag/ghc-8.0.2-bugfix-12545-backport-2017-06-08 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jun 8 00:52:51 2017 From: ghc-devs at haskell.org (GHC) Date: Thu, 08 Jun 2017 00:52:51 -0000 Subject: [GHC] #13800: ghc panic: No skolem info: s_a7aK[sk] Message-ID: <043.5dfb097ffcc0e2a2a2d4ef00d5efca40@haskell.org> #13800: ghc panic: No skolem info: s_a7aK[sk] -------------------------------------+------------------------------------- Reporter: hexo | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.2 Keywords: | Operating System: Unknown/Multiple Architecture: x86_64 | Type of failure: Compile-time (amd64) | crash or panic Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- Project is located at: https://github.com/hacxman/clock.git Uses Ivory and Tower framerworks. Error should be introduced by code in commit SSD1306 api wrapper ( https://github.com/hacxman/clock/commit/8075047381e3bcc572c2c12ccf83fd9410ee285f ) in file src/Clock/SSD1306.hs lines 32-67. When I run make blink-test, this happens: stack build . --exec 'blink-test-gen --src-dir=build/blink-test --const- fold --verbose' clock-0.1.0.0: build Preprocessing library clock-0.1.0.0... [5 of 7] Compiling Clock.SSD1306 ( src/Clock/SSD1306.hs, .stack- work/dist/x86_64-linux/Cabal-1.24.2.0/build/Clock/SSD1306.o ) /home/mzatko/src/embedded/clock/src/Clock/SSD1306.hs:241:11: error:ghc: panic! (the 'impossible' happened) (GHC version 8.0.2 for x86_64-unknown-linux): No skolem info: s_a7aK[sk] Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug -- While building package clock-0.1.0.0 using: /home/mzatko/.stack/setup-exe-cache/x86_64-linux/setup-Simple- Cabal-1.24.2.0-ghc-8.0.2 --builddir=.stack- work/dist/x86_64-linux/Cabal-1.24.2.0 build lib:clock exe:blink-test-gen exe:oled-test-gen --ghc-options " -ddump-hi -ddump-to-file" Process exited with code: ExitFailure 1 Makefile:50: recipe for target 'blink-test' failed make: *** [blink-test] Error 1 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jun 8 06:15:35 2017 From: ghc-devs at haskell.org (GHC) Date: Thu, 08 Jun 2017 06:15:35 -0000 Subject: [GHC] #13666: The gcc wrapper can't handle trailing backslashes In-Reply-To: <046.48bb815bdf014d4f8613c4501cc5c3f5@haskell.org> References: <046.48bb815bdf014d4f8613c4501cc5c3f5@haskell.org> Message-ID: <061.4d2c9b362805e88d64f3ef585a725a52@haskell.org> #13666: The gcc wrapper can't handle trailing backslashes ---------------------------------+---------------------------------------- Reporter: niklasl | Owner: (none) Type: bug | Status: patch Priority: low | Milestone: Component: Driver | Version: 8.0.1 Resolution: | Keywords: Operating System: Windows | Architecture: Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #13709 | Differential Rev(s): Phab:D3628 Wiki Page: | ---------------------------------+---------------------------------------- Comment (by Tamar Christina ): In [changeset:"bca56bd040de64315564cdac4b7e943fc8a75ea0/ghc" bca56bd/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="bca56bd040de64315564cdac4b7e943fc8a75ea0" Fix slash escaping in cwrapper.c Summary: Escape `\` in paths on Windows in `cwapper.c` when we re-output the paths. Test Plan: ./validate Reviewers: austin, bgamari Reviewed By: bgamari Subscribers: rwbarton, thomie GHC Trac Issues: #13666 Differential Revision: https://phabricator.haskell.org/D3628 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jun 8 06:17:08 2017 From: ghc-devs at haskell.org (GHC) Date: Thu, 08 Jun 2017 06:17:08 -0000 Subject: [GHC] #13666: The gcc wrapper can't handle trailing backslashes In-Reply-To: <046.48bb815bdf014d4f8613c4501cc5c3f5@haskell.org> References: <046.48bb815bdf014d4f8613c4501cc5c3f5@haskell.org> Message-ID: <061.b5790fa741d276a4841a779e52a93e50@haskell.org> #13666: The gcc wrapper can't handle trailing backslashes ---------------------------------+---------------------------------------- Reporter: niklasl | Owner: (none) Type: bug | Status: closed Priority: low | Milestone: Component: Driver | Version: 8.0.1 Resolution: fixed | Keywords: Operating System: Windows | Architecture: Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #13709 | Differential Rev(s): Phab:D3628 Wiki Page: | ---------------------------------+---------------------------------------- Changes (by Phyx-): * status: patch => closed * resolution: => fixed -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jun 8 07:38:17 2017 From: ghc-devs at haskell.org (GHC) Date: Thu, 08 Jun 2017 07:38:17 -0000 Subject: [GHC] #13751: Runtime crash with <> after concurrent stressing of STM computations In-Reply-To: <046.2e620bb56fd39fe88732c85fa515dde8@haskell.org> References: <046.2e620bb56fd39fe88732c85fa515dde8@haskell.org> Message-ID: <061.60a2ae7758c99c4cc2e4d9aabc9578e5@haskell.org> #13751: Runtime crash with <> after concurrent stressing of STM computations -------------------------------------+------------------------------------- Reporter: literon | Owner: simonmar Type: bug | Status: new Priority: highest | Milestone: 8.2.1 Component: Runtime System | Version: 8.0.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Runtime crash | Test Case: Blocked By: | Blocking: Related Tickets: 10414 | Differential Rev(s): Phab:D3630 Wiki Page: | -------------------------------------+------------------------------------- Comment (by Simon Marlow ): In [changeset:"598472908ebb08f6811b892f285490554c290ae3/ghc" 5984729/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="598472908ebb08f6811b892f285490554c290ae3" Fix a lost-wakeup bug in BLACKHOLE handling (#13751) Summary: The problem occurred when * Threads A & B evaluate the same thunk * Thread A context-switches, so the thunk gets blackholed * Thread C enters the blackhole, creates a BLOCKING_QUEUE attached to the blackhole and thread A's `tso->bq` queue * Thread B updates the blackhole with a value, overwriting the BLOCKING_QUEUE * We GC, replacing A's update frame with stg_enter_checkbh * Throw an exception in A, which ignores the stg_enter_checkbh frame Now we have C blocked on A's tso->bq queue, but we forgot to check the queue because the stg_enter_checkbh frame has been thrown away by the exception. The solution and alternative designs are discussed in Note [upd-black- hole]. This also exposed a bug in the interpreter, whereby we were sometimes context-switching without calling `threadPaused()`. I've fixed this and added some Notes. Test Plan: * `cd testsuite/tests/concurrent && make slow` * validate Reviewers: niteria, bgamari, austin, erikd Reviewed By: erikd Subscribers: rwbarton, thomie GHC Trac Issues: #13751 Differential Revision: https://phabricator.haskell.org/D3630 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jun 8 07:39:05 2017 From: ghc-devs at haskell.org (GHC) Date: Thu, 08 Jun 2017 07:39:05 -0000 Subject: [GHC] #13751: Runtime crash with <> after concurrent stressing of STM computations In-Reply-To: <046.2e620bb56fd39fe88732c85fa515dde8@haskell.org> References: <046.2e620bb56fd39fe88732c85fa515dde8@haskell.org> Message-ID: <061.aad505b55d0697c3f375fded70639372@haskell.org> #13751: Runtime crash with <> after concurrent stressing of STM computations -------------------------------------+------------------------------------- Reporter: literon | Owner: simonmar Type: bug | Status: merge Priority: highest | Milestone: 8.2.1 Component: Runtime System | Version: 8.0.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Runtime crash | Test Case: Blocked By: | Blocking: Related Tickets: 10414 | Differential Rev(s): Phab:D3630 Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonmar): * status: new => merge -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jun 8 09:58:59 2017 From: ghc-devs at haskell.org (GHC) Date: Thu, 08 Jun 2017 09:58:59 -0000 Subject: [GHC] #13801: Make -main-is work with {thing} from arbitrary installed packages Message-ID: <050.8f0a9982543076f1b76bf433056aad58@haskell.org> #13801: Make -main-is work with {thing} from arbitrary installed packages -------------------------------------+------------------------------------- Reporter: SimonHengel | Owner: (none) Type: feature | Status: new request | Priority: normal | Milestone: Component: Compiler | Version: 8.0.2 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- = TL;DR Conceptually, `-main-is {thing}` is useful when writing unit tests. It allows you to test the code in your "Main" module by allowing you to use a different name for it. But using it that way will always result in double compilation (that is, all your code has to be compiled twice, once for your executable and once for your test suite). The reason for this is that `{thing}` has to be part of the currently compiled package (aka the `main` package). As a consequent, when using `-is-main`, it is not possible to define a library that is used by both the executable and the test suite. I propose that `-main-is` is extended so that `{thing}` can be from any ''installed package''. I'll give a somewhat detailed motivation below. Please feel free to fast- forward to the last section, which gives a test case (or rather acceptance criteria) for this feature request. = The full story == How to unit test code without the use of {{{-main-is}}} This section shows a common way to structure code for an executable, so that it is possible to: 1. write unit tests for all the code 1. avoid double compilation between the executable and the test suite (for the reminder of this text I call these two properties ''desirable properties'') === Code as a library Define all your code outside of `Main`, including your `main` function. As an example, let's assume we define our code in `src/My/Awesome/Tool.hs`, which defines the module `My.Awesome.Tool` and a "main" function named `run` in it: {{{#!hs -- src/My/Awesome/Tool.hs module My.Awesome.Tool where run :: IO () run = do ... }}} === Tests that use the library It is then possible to write tests for that code by importing the library module, e.g.: {{{#!hs -- test/Main.hs module Main where imports My.Awesome.Tool main = do -- unit tests go here ... }}} === Executable as a thin wrapper around the library code To compile an actual executable we create a ''driver''. The driver imports the library module and defines a `main` function. For our example this would looks something like this: {{{#!hs -- driver/Main.hs module Main where import My.Awesome.Tool (run) main = run }}} '''Note:''' The driver does not define any non-trivial code. This is to retain our first desirable property. === Compiling everything with Cabal It is then possible to compile everything with Cabal, using a Cabal file similar to this one: {{{ -- my-awesome-tool.cabal name: my-awesome-tool library hs-source-dirs: src exposed-modules: My.Awesome.Tool test-suite test type: exitcode-stdio-1.0 build-depends: my-awesome-tool hs-source-dirs: test main-is: Main.hs executable my-awesome-tool build-depends: my-awesome-tool hs-source-dirs: driver main-is: Main.hs }}} '''Note:''' Both, the executable and the test suite depend on the library component. This avoids double compilation, one of our desirable properties. == Removing the need for a driver by using `-main-is` It is possible to get rid of the need for a driver by using `-main-is`: {{{ -- my-awesome-tool.cabal ... executable my-awesome-tool hs-source-dirs: src main-is: My/Awesome/Tool.hs ghc-options: -main-is My.Awesome.Tool.run }}} But doing so results in double compilation: The executable can no longer depend on the library component. This is expected behavior, as stated in the documentation: > Strictly speaking, `-main-is` is not a link-phase flag at all; it has no effect on the link step. The flag must be specified when compiling the module containing the specified main function == Shortcomings of `-main-is` According to the documentation, the purpose of `-main-is` is: > When testing, it is often convenient to change which function is the “main” one, and the `-main-is` flag allows you to do so. It is not very explicit what "when testing" refers to here, but for the lack of any other evidence I assume this refers to unit testing. As far as I can tell, there is no way to use `-main-is` for unit testing without double compilation. '''Or in other words:''' If we use `-main-is` for it's stated purpose we always loose the second of our desirable properties. Please correct me if you think that I'm wrong. == How is `-main-is` implemented? I haven't looked at any code, but my assumption is that GHC generates a driver module, similar to the one we have to write by hand if we don't use `-main-is`. Can somebody confirm (or negate) this? == Proposed change I propose that GHC always generates the driver when `-main-is {thing}` is specified. GHC should even generate the driver if `{thing}` is not part of the currently compiled package (specifically `{thing}` is defined in an ''installed package'', not the `main` package). == (manual) test case This test case uses my `hpack` package (but any package that defines some function of type `IO ()` should work): {{{ $ cabal install hpack $ ghc -package hpack -main-is Hpack.main -o hpack }}} === expected result An executable named `hpack` is compiled that uses `Hpack.main` from the installed package `hpack` as entry point. === actual result {{{ ghc: no input files Usage: For basic information, try the `--help' option. }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jun 8 10:01:04 2017 From: ghc-devs at haskell.org (GHC) Date: Thu, 08 Jun 2017 10:01:04 -0000 Subject: [GHC] #13801: Make -main-is work with {thing} from arbitrary installed packages In-Reply-To: <050.8f0a9982543076f1b76bf433056aad58@haskell.org> References: <050.8f0a9982543076f1b76bf433056aad58@haskell.org> Message-ID: <065.b6a5443dd7602273ab287a83cf244bc2@haskell.org> #13801: Make -main-is work with {thing} from arbitrary installed packages -------------------------------------+------------------------------------- Reporter: SimonHengel | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by SimonHengel): A related `hpack` issue: https://github.com/sol/hpack/issues/173#issue-229003256 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jun 8 10:35:48 2017 From: ghc-devs at haskell.org (GHC) Date: Thu, 08 Jun 2017 10:35:48 -0000 Subject: [GHC] #13802: Installation of yesod-auth-1.4.13.2 fails with "ghc: panic! (the 'impossible' happened)" Message-ID: <043.1f3d248765c4d66da4ba309745c7dadb@haskell.org> #13802: Installation of yesod-auth-1.4.13.2 fails with "ghc: panic! (the 'impossible' happened)" -------------------------------------+------------------------------------- Reporter: nvbt | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.2 Keywords: panic, stack, | Operating System: MacOS X install | Architecture: | Type of failure: Compile-time Unknown/Multiple | crash or panic Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- I wanted to install hledger-web via "stack install hledger-web" which runs until it hits (this is the full output of the command, emphasis [+] was added): {{{ yesod-auth-1.4.13.2: configure yesod-auth-1.4.13.2: build Progress: 1/3 -- While building package yesod-auth-1.4.13.2 using: /Users/manuel/.stack/setup-exe-cache/x86_64-osx/Cabal- simple_mPHDZzAJ_1.22.5.0_ghc-7.10.3 --builddir=.stack- work/dist/x86_64-osx/Cabal-1.22.5.0 build --ghc-options " -ddump-hi -ddump-to-file" Process exited with code: ExitFailure 1 Logs have been written to: /Users/manuel/.stack/global-project/.stack- work/logs/yesod-auth-1.4.13.2.log Configuring yesod-auth-1.4.13.2... Building yesod-auth-1.4.13.2... Preprocessing library yesod-auth-1.4.13.2... [ 1 of 12] Compiling Yesod.PasswordStore ( Yesod/PasswordStore.hs, .stack-work/dist/x86_64-osx/Cabal-1.22.5.0/build/Yesod/PasswordStore.o ) /private/var/folders/36/cmdfg5j90vjgjww3qjnvhkhw0000gn/T/stack34153 /yesod-auth-1.4.13.2/Yesod/PasswordStore.hs:166:31: Warning: Defaulting the following constraint(s) to type ‘Integer’ (Integral b0) arising from a use of ‘^’ at Yesod/PasswordStore.hs:166:31 (Num b0) arising from the literal ‘32’ at Yesod/PasswordStore.hs:166:32-33 In the first argument of ‘(-)’, namely ‘2 ^ 32’ In the first argument of ‘(*)’, namely ‘(2 ^ 32 - 1)’ In the second argument of ‘(>)’, namely ‘(2 ^ 32 - 1) * hLen’ /private/var/folders/36/cmdfg5j90vjgjww3qjnvhkhw0000gn/T/stack34153 /yesod-auth-1.4.13.2/Yesod/PasswordStore.hs:419:1: Warning: Defined but not used: ‘toStrict’ /private/var/folders/36/cmdfg5j90vjgjww3qjnvhkhw0000gn/T/stack34153 /yesod-auth-1.4.13.2/Yesod/PasswordStore.hs:422:1: Warning: Defined but not used: ‘fromStrict’ [ 2 of 12] Compiling Yesod.Auth.Message ( Yesod/Auth/Message.hs, .stack-work/dist/x86_64-osx/Cabal-1.22.5.0/build/Yesod/Auth/Message.o ) /private/var/folders/36/cmdfg5j90vjgjww3qjnvhkhw0000gn/T/stack34153 /yesod-auth-1.4.13.2/Yesod/Auth/Message.hs:23:1: Warning: The import of ‘mappend’ from module ‘Data.Monoid’ is redundant /private/var/folders/36/cmdfg5j90vjgjww3qjnvhkhw0000gn/T/stack34153 /yesod-auth-1.4.13.2/Yesod/Auth/Message.hs:698:1: Warning: Defined but not used: ‘croatianMessage’ /private/var/folders/36/cmdfg5j90vjgjww3qjnvhkhw0000gn/T/stack34153 /yesod-auth-1.4.13.2/Yesod/Auth/Message.hs:459:1: Warning: Pattern match(es) are overlapped In an equation for ‘finnishMessage’: finnishMessage Password = ... /private/var/folders/36/cmdfg5j90vjgjww3qjnvhkhw0000gn/T/stack34153 /yesod-auth-1.4.13.2/Yesod/Auth/Message.hs:459:1: Warning: Pattern match(es) are non-exhaustive In an equation for ‘finnishMessage’: Patterns not matched: CurrentPassword [ 3 of 12] Compiling Yesod.Auth.Routes ( Yesod/Auth/Routes.hs, .stack- work/dist/x86_64-osx/Cabal-1.22.5.0/build/Yesod/Auth/Routes.o ) [ 4 of 12] Compiling Yesod.Auth ( Yesod/Auth.hs, .stack- work/dist/x86_64-osx/Cabal-1.22.5.0/build/Yesod/Auth.o ) [++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++] ghc: panic! (the 'impossible' happened) (GHC version 7.10.3 for x86_64-apple-darwin): Loading temp shared object failed: dlopen(/var/folders/36/cmdfg5j90vjgjww3qjnvhkhw0000gn/T/ghc34454_0/libghc_21.dylib, 5): no suitable image found. Did find: /var/folders/36/cmdfg5j90vjgjww3qjnvhkhw0000gn/T/ghc34454_0/libghc_21.dylib: malformed mach-o: load commands size (35400) > 32768 [++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++] Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug }}} I have tried this installation multiple times over the last weeks, and have always failed with this error message. If any further assistance is needed I will be happy to help. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jun 8 12:25:56 2017 From: ghc-devs at haskell.org (GHC) Date: Thu, 08 Jun 2017 12:25:56 -0000 Subject: [GHC] #13803: Panic while forcing the thunk for TyThing IsFile (regression) Message-ID: <044.5fd6949417f66553983c80f17489c157@haskell.org> #13803: Panic while forcing the thunk for TyThing IsFile (regression) -------------------------------------+------------------------------------- Reporter: inaki | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.1-rc2 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: Compile-time Unknown/Multiple | crash or panic Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- (Apologies in advance for the very non-minimal testcase. I have been unsuccessfully trying to reduce the testcase for a few hours now, but I am flying blind, and the bug seems to depend on the interaction of various modules. The panic is very reproducible for me, so I figured that better reporting even if I failed to obtain a simplified testcase. Maybe someone else has more luck isolating the issue.) When compiling `gi-gio-2.0.12` I consistently get the following GHC panic: {{{ [259 of 293] Compiling GI.Gio.Interfaces.File ( GI/Gio/Interfaces/File.hs, dist/build/GI/Gio/Interfaces/File.o ) ghc: panic! (the 'impossible' happened) (GHC version 8.2.0.20170507 for x86_64-unknown-linux): tcIfaceGlobal (local): not found You are in a maze of twisty little passages, all alike. While forcing the thunk for TyThing IsFile which was lazily initialized by initIfaceCheck typecheckLoop, I tried to tie the knot, but I couldn't find IsFile in the current type environment. If you are developing GHC, please read Note [Tying the knot] and Note [Type-checking inside the knot]. Consider rebuilding GHC with profiling for a better stack trace. Contents of current type environment: [] Call stack: CallStack (from HasCallStack): prettyCurrentCallStack, called at compiler/utils/Outputable.hs:1134:58 in ghc:Outputable callStackDoc, called at compiler/utils/Outputable.hs:1138:37 in ghc:Outputable pprPanic, called at compiler/iface/TcIface.hs:1689:23 in ghc:TcIface Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug }}} To compile this code you will need the `glib2-devel` package installed. To compile {{{ $ cabal get gi-gio-2.0.12 $ cd gi-gio-2.0.12 $ cabal sandbox init $ cabal install --dependencies-only $ cabal build }}} I am running version `8.2.0.20170507`, from https://copr.fedorainfracloud.org/coprs/petersen/ghc-8.2.1/ . The same code compiles in versions `7.8.x`, `7.10.x` and `8.0.x`. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jun 8 12:33:52 2017 From: ghc-devs at haskell.org (GHC) Date: Thu, 08 Jun 2017 12:33:52 -0000 Subject: [GHC] #13803: Panic while forcing the thunk for TyThing IsFile (regression) In-Reply-To: <044.5fd6949417f66553983c80f17489c157@haskell.org> References: <044.5fd6949417f66553983c80f17489c157@haskell.org> Message-ID: <059.a8b93271a70458fb834d04350c1f3a5c@haskell.org> #13803: Panic while forcing the thunk for TyThing IsFile (regression) -------------------------------------+------------------------------------- Reporter: inaki | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.1-rc2 Resolution: | Keywords: hs-boot Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by inaki): * keywords: => hs-boot Comment: A possibly related issue is [ticket:13710], although in the current code there are no record wildcards involved. I haven't tried the fix in issue:13710#comment:12. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jun 8 12:43:42 2017 From: ghc-devs at haskell.org (GHC) Date: Thu, 08 Jun 2017 12:43:42 -0000 Subject: [GHC] #13800: ghc panic: No skolem info: s_a7aK[sk] In-Reply-To: <043.5dfb097ffcc0e2a2a2d4ef00d5efca40@haskell.org> References: <043.5dfb097ffcc0e2a2a2d4ef00d5efca40@haskell.org> Message-ID: <058.e4ab2fd087300bf7e53cbdaef844c4b6@haskell.org> #13800: ghc panic: No skolem info: s_a7aK[sk] -------------------------------------+------------------------------------- Reporter: hexo | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: x86_64 Type of failure: Compile-time | (amd64) crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by mpickering): I tried reproducing this but didn't get very far. The project has a lot of dependencies, please can you provide a reproduction or precise instructions to build the project which don't involve stack? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jun 8 12:49:03 2017 From: ghc-devs at haskell.org (GHC) Date: Thu, 08 Jun 2017 12:49:03 -0000 Subject: [GHC] #13800: ghc panic: No skolem info: s_a7aK[sk] In-Reply-To: <043.5dfb097ffcc0e2a2a2d4ef00d5efca40@haskell.org> References: <043.5dfb097ffcc0e2a2a2d4ef00d5efca40@haskell.org> Message-ID: <058.11700c9c96c6abfcabafc4a01b3d714c@haskell.org> #13800: ghc panic: No skolem info: s_a7aK[sk] -------------------------------------+------------------------------------- Reporter: hexo | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: x86_64 Type of failure: Compile-time | (amd64) crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): There are some fixed bugs wtih this error message; e.g. #13393 Could you possibly try with 8.2? Simon -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jun 8 13:00:19 2017 From: ghc-devs at haskell.org (GHC) Date: Thu, 08 Jun 2017 13:00:19 -0000 Subject: [GHC] #13803: Panic while forcing the thunk for TyThing IsFile (regression) In-Reply-To: <044.5fd6949417f66553983c80f17489c157@haskell.org> References: <044.5fd6949417f66553983c80f17489c157@haskell.org> Message-ID: <059.234b42496510122e5dde3e2959af45d2@haskell.org> #13803: Panic while forcing the thunk for TyThing IsFile (regression) -------------------------------------+------------------------------------- Reporter: inaki | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.1-rc2 Resolution: | Keywords: hs-boot Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by ezyang): Is it possible for you to at least post the autogenerated source code that the Setup script generates? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jun 8 13:05:47 2017 From: ghc-devs at haskell.org (GHC) Date: Thu, 08 Jun 2017 13:05:47 -0000 Subject: [GHC] #13750: GHC produces incorrect coercions in hairy code In-Reply-To: <045.2957c281e52a0617c4b44226d50f7bbc@haskell.org> References: <045.2957c281e52a0617c4b44226d50f7bbc@haskell.org> Message-ID: <060.646e9d9fd9bd9b2ec6c14452146ba086@haskell.org> #13750: GHC produces incorrect coercions in hairy code -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: (none) Type: bug | Status: new Priority: highest | Milestone: 8.2.2 Component: Compiler | Version: 8.2.1-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Runtime crash | Test Case: Blocked By: | Blocking: Related Tickets: #13429 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by kosmikus): Looks good. I built from git master, and it works for me now. Feel free to close. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jun 8 13:17:09 2017 From: ghc-devs at haskell.org (GHC) Date: Thu, 08 Jun 2017 13:17:09 -0000 Subject: [GHC] #13803: Panic while forcing the thunk for TyThing IsFile (regression) In-Reply-To: <044.5fd6949417f66553983c80f17489c157@haskell.org> References: <044.5fd6949417f66553983c80f17489c157@haskell.org> Message-ID: <059.6eda0294fe919b251132e3e25647e45a@haskell.org> #13803: Panic while forcing the thunk for TyThing IsFile (regression) -------------------------------------+------------------------------------- Reporter: inaki | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.1-rc2 Resolution: | Keywords: hs-boot Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by inaki): Sure, here it is: https://www.mpp.mpg.de/~inaki/gi-gio-2.0.12.tar.gz -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jun 8 13:48:42 2017 From: ghc-devs at haskell.org (GHC) Date: Thu, 08 Jun 2017 13:48:42 -0000 Subject: [GHC] #13750: GHC produces incorrect coercions in hairy code In-Reply-To: <045.2957c281e52a0617c4b44226d50f7bbc@haskell.org> References: <045.2957c281e52a0617c4b44226d50f7bbc@haskell.org> Message-ID: <060.27280da071a2c5659b39131fc408f019@haskell.org> #13750: GHC produces incorrect coercions in hairy code -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: (none) Type: bug | Status: closed Priority: highest | Milestone: 8.2.2 Component: Compiler | Version: 8.2.1-rc2 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Runtime crash | Test Case: Blocked By: | Blocking: Related Tickets: #13429 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * status: new => closed * resolution: => fixed Comment: Hurrah. Thanks. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jun 8 13:49:39 2017 From: ghc-devs at haskell.org (GHC) Date: Thu, 08 Jun 2017 13:49:39 -0000 Subject: [GHC] #13429: Optimizer produces Core with an infinite <> In-Reply-To: <045.cf5ba15167896826f7f0c0a59d69b609@haskell.org> References: <045.cf5ba15167896826f7f0c0a59d69b609@haskell.org> Message-ID: <060.a8ea703a6fdb968cb96a8b7cf56f3c89@haskell.org> #13429: Optimizer produces Core with an infinite <> -------------------------------------+------------------------------------- Reporter: lehins | Owner: simonpj Type: bug | Status: merge Priority: highest | Milestone: 8.2.1 Component: Compiler | Version: 8.0.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Runtime crash | Test Case: | simplCore/should_run/T13429, | T13429_2 Blocked By: | Blocking: Related Tickets: #13750, #12545 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): Remarkably, this patch also apparently fixed #13750 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jun 8 17:46:53 2017 From: ghc-devs at haskell.org (GHC) Date: Thu, 08 Jun 2017 17:46:53 -0000 Subject: [GHC] #13803: Panic while forcing the thunk for TyThing IsFile (regression) In-Reply-To: <044.5fd6949417f66553983c80f17489c157@haskell.org> References: <044.5fd6949417f66553983c80f17489c157@haskell.org> Message-ID: <059.939c3cb947df9271dc83f0b916d24be4@haskell.org> #13803: Panic while forcing the thunk for TyThing IsFile (regression) -------------------------------------+------------------------------------- Reporter: inaki | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.1-rc2 Resolution: | Keywords: hs-boot Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): Minimizing this bug is probably going to take off a couple years of my life... But in any case, I've managed to reduce this down to six (!) files with one external dependency (`haskell-gi-base`): {{{#!hs module GIGioInterfacesFile where import Data.GI.Base.ShortPrelude -- from haskell-gi-base import {-# SOURCE #-} qualified GIGioObjectsFileEnumerator as Gio.FileEnumerator import {-# SOURCE #-} qualified GIGioObjectsMountOperation as Gio.MountOperation class IsFile o }}} {{{#!hs module GIGioInterfacesFile where class IsFile o }}} {{{#!hs {-# LANGUAGE ConstraintKinds #-} {-# LANGUAGE DataKinds #-} {-# LANGUAGE TypeFamilies #-} module GIGioObjectsFileEnumerator where import GHC.Exts (Constraint) import {-# SOURCE #-} qualified GIGioInterfacesFile as Gio.File class IsFileEnumerator o class AttrInfo info where type family AttrSetTypeConstraint info :: * -> Constraint data FileEnumeratorContainerPropertyInfo instance AttrInfo FileEnumeratorContainerPropertyInfo where type AttrSetTypeConstraint FileEnumeratorContainerPropertyInfo = Gio.File.IsFile }}} {{{#!hs module GIGioObjectsFileEnumerator where class IsFileEnumerator o }}} {{{#!hs module GIGioObjectsMountOperation where class IsMountOperation o }}} {{{#!hs module GIGioObjectsMountOperation where class IsMountOperation o }}} {{{ $ /opt/ghc/8.2.1/bin/ghci GIGioInterfacesFile.hs GHCi, version 8.2.0.20170522: http://www.haskell.org/ghc/ :? for help Loaded GHCi configuration from /home/rgscott/.ghci [1 of 6] Compiling GIGioInterfacesFile[boot] ( GIGioInterfacesFile.hs- boot, interpreted ) [2 of 6] Compiling GIGioObjectsFileEnumerator[boot] ( GIGioObjectsFileEnumerator.hs-boot, interpreted ) [3 of 6] Compiling GIGioObjectsFileEnumerator ( GIGioObjectsFileEnumerator.hs, interpreted ) [4 of 6] Compiling GIGioObjectsMountOperation[boot] ( GIGioObjectsMountOperation.hs-boot, interpreted ) [5 of 6] Compiling GIGioInterfacesFile ( GIGioInterfacesFile.hs, interpreted ) ghc: panic! (the 'impossible' happened) (GHC version 8.2.0.20170522 for x86_64-unknown-linux): tcIfaceGlobal (local): not found You are in a maze of twisty little passages, all alike. While forcing the thunk for TyThing IsFile which was lazily initialized by initIfaceCheck typecheckLoop, I tried to tie the knot, but I couldn't find IsFile in the current type environment. If you are developing GHC, please read Note [Tying the knot] and Note [Type-checking inside the knot]. Consider rebuilding GHC with profiling for a better stack trace. Contents of current type environment: [] Call stack: CallStack (from HasCallStack): prettyCurrentCallStack, called at compiler/utils/Outputable.hs:1133:58 in ghc:Outputable callStackDoc, called at compiler/utils/Outputable.hs:1137:37 in ghc:Outputable pprPanic, called at compiler/iface/TcIface.hs:1689:23 in ghc:TcIface }}} The annoying bit is that I haven't figure out how to eliminate that `import Data.GI.Base.ShortPrelude` from the `haskell-gi-base` library. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jun 8 18:44:51 2017 From: ghc-devs at haskell.org (GHC) Date: Thu, 08 Jun 2017 18:44:51 -0000 Subject: [GHC] #13801: Make -main-is work with {thing} from arbitrary installed packages In-Reply-To: <050.8f0a9982543076f1b76bf433056aad58@haskell.org> References: <050.8f0a9982543076f1b76bf433056aad58@haskell.org> Message-ID: <065.e0570bf6e1343e147bb5e6ec0df97d65@haskell.org> #13801: Make -main-is work with {thing} from arbitrary installed packages -------------------------------------+------------------------------------- Reporter: SimonHengel | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * cc: ezyang (added) Comment: CCing ezyang due to his interest in package system concerns. > I haven't looked at any code, but my assumption is that GHC generates a driver module, similar to the one we have to write by hand if we don't use -main-is. Can somebody confirm (or negate) this? I believe this is partially true. However, it's a bit tricky; we don't actually generate a module. We merely emit a binding which claims to be from another module when typechecking what the user says should be the main module. Have a look at `Note [Root-main Id]` for details. On the whole this sounds fairly easy to do. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jun 8 18:45:13 2017 From: ghc-devs at haskell.org (GHC) Date: Thu, 08 Jun 2017 18:45:13 -0000 Subject: [GHC] #13803: Panic while forcing the thunk for TyThing IsFile (regression) In-Reply-To: <044.5fd6949417f66553983c80f17489c157@haskell.org> References: <044.5fd6949417f66553983c80f17489c157@haskell.org> Message-ID: <059.0a8e19c28c651dea00cda2a656b20aad@haskell.org> #13803: Panic while forcing the thunk for TyThing IsFile (regression) -------------------------------------+------------------------------------- Reporter: inaki | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.1-rc2 Resolution: | Keywords: hs-boot Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): Hrm, it looks like you could also use this instead for `GIGioInterfacesFile.hs`: {{{#!hs module GIGioInterfacesFile where import Data.Text import {-# SOURCE #-} qualified GIGioObjectsFileEnumerator as Gio.FileEnumerator import {-# SOURCE #-} qualified GIGioObjectsMountOperation as Gio.MountOperation class IsFile o }}} That still requires an external dependency (`text`), but it's a far easier dependency to install than `haskell-gi-base`, at least. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jun 8 18:46:52 2017 From: ghc-devs at haskell.org (GHC) Date: Thu, 08 Jun 2017 18:46:52 -0000 Subject: [GHC] #13803: Panic while forcing the thunk for TyThing IsFile (regression) In-Reply-To: <044.5fd6949417f66553983c80f17489c157@haskell.org> References: <044.5fd6949417f66553983c80f17489c157@haskell.org> Message-ID: <059.b6d5b03ff2fe47a670f6e1b182ca546f@haskell.org> #13803: Panic while forcing the thunk for TyThing IsFile (regression) -------------------------------------+------------------------------------- Reporter: inaki | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.1-rc2 Resolution: | Keywords: hs-boot Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): I can also confirm that the workaround that ezyang posted in https://ghc.haskell.org/trac/ghc/ticket/13710#comment:12 does //not// fix this problem. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jun 8 19:05:04 2017 From: ghc-devs at haskell.org (GHC) Date: Thu, 08 Jun 2017 19:05:04 -0000 Subject: [GHC] #13803: Panic while forcing the thunk for TyThing IsFile (regression) In-Reply-To: <044.5fd6949417f66553983c80f17489c157@haskell.org> References: <044.5fd6949417f66553983c80f17489c157@haskell.org> Message-ID: <059.768529dfac44f9115c05b9b25846680a@haskell.org> #13803: Panic while forcing the thunk for TyThing IsFile (regression) -------------------------------------+------------------------------------- Reporter: inaki | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.1-rc2 Resolution: | Keywords: hs-boot Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): OK, here's a version of `GIGioInterfacesFile` with no external dependencies: {{{#!hs module GIGioInterfacesFile where import Control.DeepSeq () import {-# SOURCE #-} qualified GIGioObjectsFileEnumerator as Gio.FileEnumerator import {-# SOURCE #-} qualified GIGioObjectsMountOperation as Gio.MountOperation class IsFile o }}} I have yet to figure out why the import of `Control.DeepSeq` is needed here. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jun 8 19:10:54 2017 From: ghc-devs at haskell.org (GHC) Date: Thu, 08 Jun 2017 19:10:54 -0000 Subject: [GHC] #11501: Building nofib/fibon returns permission denied In-Reply-To: <042.7732253ef90810c7acc41907aecb19ff@haskell.org> References: <042.7732253ef90810c7acc41907aecb19ff@haskell.org> Message-ID: <057.5ccecec6ca6692fc41dfcaa736b58aaf@haskell.org> #11501: Building nofib/fibon returns permission denied -------------------------------------+------------------------------------- Reporter: rem | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: NoFib benchmark | Version: 7.10.3 suite | Resolution: | Keywords: Operating System: Linux | Architecture: x86_64 | (amd64) Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by michalt): @bgamari/gracjan: Now that `fibon` is gone, should we close this ticket or re-purpose it for `nofib` improvements? (I don't feel strongly either way, but I did find your discussion quite interesting) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jun 8 19:31:42 2017 From: ghc-devs at haskell.org (GHC) Date: Thu, 08 Jun 2017 19:31:42 -0000 Subject: [GHC] #13710: panic with boot and -jX In-Reply-To: <044.0eeac669ba8b5eeee057a55613b1dd46@haskell.org> References: <044.0eeac669ba8b5eeee057a55613b1dd46@haskell.org> Message-ID: <059.ccff273b38a4d47847b25678a28f6cf7@haskell.org> #13710: panic with boot and -jX -------------------------------------+------------------------------------- Reporter: pacak | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.1-rc2 Resolution: | Keywords: hs-boot Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): Now with even fewer //internal// dependencies: {{{#!hs {-# LANGUAGE TypeFamilies #-} module D (D) where type family D a type instance D Int = Int }}} {{{#!hs module GIGioInterfacesFile where import D () import {-# SOURCE #-} qualified GIGioObjectsFileEnumerator as Gio.FileEnumerator import {-# SOURCE #-} qualified GIGioObjectsMountOperation as Gio.MountOperation class IsFile o }}} It looks like type family instances are the culprit. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jun 8 19:32:36 2017 From: ghc-devs at haskell.org (GHC) Date: Thu, 08 Jun 2017 19:32:36 -0000 Subject: [GHC] #13710: panic with boot and -jX In-Reply-To: <044.0eeac669ba8b5eeee057a55613b1dd46@haskell.org> References: <044.0eeac669ba8b5eeee057a55613b1dd46@haskell.org> Message-ID: <059.749ec51875b7473d8fd69d5e1302c8cf@haskell.org> #13710: panic with boot and -jX -------------------------------------+------------------------------------- Reporter: pacak | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.1-rc2 Resolution: | Keywords: hs-boot Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): Oops, sorry, comment:13 was meant for #13803. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jun 8 19:32:51 2017 From: ghc-devs at haskell.org (GHC) Date: Thu, 08 Jun 2017 19:32:51 -0000 Subject: [GHC] #13803: Panic while forcing the thunk for TyThing IsFile (regression) In-Reply-To: <044.5fd6949417f66553983c80f17489c157@haskell.org> References: <044.5fd6949417f66553983c80f17489c157@haskell.org> Message-ID: <059.59ead5d34b645e4d6162296e01fc57ad@haskell.org> #13803: Panic while forcing the thunk for TyThing IsFile (regression) -------------------------------------+------------------------------------- Reporter: inaki | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.1-rc2 Resolution: | Keywords: hs-boot Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): Now with even fewer //internal// dependencies: {{{#!hs {-# LANGUAGE TypeFamilies #-} module D (D) where type family D a type instance D Int = Int }}} {{{#!hs module GIGioInterfacesFile where import D () import {-# SOURCE #-} qualified GIGioObjectsFileEnumerator as Gio.FileEnumerator import {-# SOURCE #-} qualified GIGioObjectsMountOperation as Gio.MountOperation class IsFile o }}} It looks like type family instances are the culprit. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jun 8 19:36:12 2017 From: ghc-devs at haskell.org (GHC) Date: Thu, 08 Jun 2017 19:36:12 -0000 Subject: [GHC] #13701: GHCi 2x slower without -keep-tmp-files In-Reply-To: <046.5313c8330fb56c9723008f1f4396a25a@haskell.org> References: <046.5313c8330fb56c9723008f1f4396a25a@haskell.org> Message-ID: <061.637bb89ae6cecbafb82eabc08f98cfa2@haskell.org> #13701: GHCi 2x slower without -keep-tmp-files -------------------------------------+------------------------------------- Reporter: niteria | Owner: duog Type: task | Status: patch Priority: normal | Milestone: Component: GHCi | Version: 8.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3620 Wiki Page: | -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"3ee3822ce588565e912ab6211e9d2cd545fc6ba6/ghc" 3ee3822c/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="3ee3822ce588565e912ab6211e9d2cd545fc6ba6" Refactor temp files cleanup Remove filesToNotIntermediateClean from DynFlags, create a data type FilesToClean, and change filesToClean in DynFlags to be a FilesToClean. Modify SysTools.newTempName and the Temporary constructor of PipelineMonad.PipelineOutput to take a TempFileLifetime, which specifies whether a temp file should live until the end of GhcMonad.withSession, or until the next time cleanIntermediateTempFiles is called. These changes allow the cleaning of intermediate files in GhcMake to be much more efficient. HscTypes.hptObjs is removed as it is no longer used. A new performance test T13701 is added, which passes both with and without -keep-tmp-files. The test fails by 25% without the patch, and passes when -keep-tmp-files is added. Note that there are still at two hotspots caused by algorithms quadratic in the number of modules, however neither of them allocate. They are: * DriverPipeline.compileOne'.needsLinker * GhcMake.getModLoop DriverPipeline.compileOne'.needsLinker is changed slightly to improve the situation. I don't like adding these Types to DynFlags, but they need to be seen by Dynflags, SysTools and PipelineMonad. The alternative seems to be to create a new module. Reviewers: austin, hvr, bgamari, dfeuer, niteria, simonmar, erikd Reviewed By: simonmar Subscribers: rwbarton, thomie GHC Trac Issues: #13701 Differential Revision: https://phabricator.haskell.org/D3620 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jun 8 19:36:12 2017 From: ghc-devs at haskell.org (GHC) Date: Thu, 08 Jun 2017 19:36:12 -0000 Subject: [GHC] #13789: Look into haddock performance regressions due to desugaring on -fno-code In-Reply-To: <046.0f3a5eea19c5bdebc2f7e950a2888eb7@haskell.org> References: <046.0f3a5eea19c5bdebc2f7e950a2888eb7@haskell.org> Message-ID: <061.fd18e809b9c12b2d402f2a20b5ad8004@haskell.org> #13789: Look into haddock performance regressions due to desugaring on -fno-code -------------------------------------+------------------------------------- Reporter: bgamari | Owner: duog Type: task | Status: patch Priority: normal | Milestone: 8.4.1 Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3629 Wiki Page: | -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"b10d3f36250d435f9f13079dd9e3ec1ecbb0017f/ghc" b10d3f36/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="b10d3f36250d435f9f13079dd9e3ec1ecbb0017f" Don't pass -dcore-lint to haddock in Haddock.mk This fixes the regressions in the haddock performance tests introduced in c9eb4385aad248118650725b7b699bb97ee21c0d. Reviewers: austin, bgamari Reviewed By: bgamari Subscribers: rwbarton, thomie GHC Trac Issues: #13789 Differential Revision: https://phabricator.haskell.org/D3629 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jun 8 19:36:12 2017 From: ghc-devs at haskell.org (GHC) Date: Thu, 08 Jun 2017 19:36:12 -0000 Subject: [GHC] #13756: Typo in user guide suggests that there's an -O* option In-Reply-To: <042.6a3b1c429314348df414591c312b566f@haskell.org> References: <042.6a3b1c429314348df414591c312b566f@haskell.org> Message-ID: <057.7181f0c1b122ad49656cd1eb5191e15e@haskell.org> #13756: Typo in user guide suggests that there's an -O* option -------------------------------------+------------------------------------- Reporter: nh2 | Owner: SantiM Type: bug | Status: new Priority: normal | Milestone: 8.2.1 Component: Documentation | Version: 8.0.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3631 Wiki Page: | -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"b2b416014e4276ebb660d85c3a612f7ca45ade78/ghc" b2b4160/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="b2b416014e4276ebb660d85c3a612f7ca45ade78" Correct optimization flags documentation In a previous change (commit 4fd6207ec6960c429e6a1bcbe0282f625010f52a), the users guide was moved from XML to the RST format. This process introduced a typo: "No -O*-type option specified:" was changed to "-O*" (which is not correct). This change fixes it. See result in: https://prnt.sc/fh332n Fixes ticket #13756. Reviewers: austin, bgamari Reviewed By: bgamari Subscribers: rwbarton, thomie GHC Trac Issues: #13756 Differential Revision: https://phabricator.haskell.org/D3631 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jun 8 19:37:08 2017 From: ghc-devs at haskell.org (GHC) Date: Thu, 08 Jun 2017 19:37:08 -0000 Subject: [GHC] #13789: Look into haddock performance regressions due to desugaring on -fno-code In-Reply-To: <046.0f3a5eea19c5bdebc2f7e950a2888eb7@haskell.org> References: <046.0f3a5eea19c5bdebc2f7e950a2888eb7@haskell.org> Message-ID: <061.de2a5531ecda2e8b2524a084d8d00b31@haskell.org> #13789: Look into haddock performance regressions due to desugaring on -fno-code -------------------------------------+------------------------------------- Reporter: bgamari | Owner: duog Type: task | Status: closed Priority: normal | Milestone: 8.4.1 Component: Compiler | Version: 8.0.1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3629 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: patch => closed * resolution: => fixed -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jun 8 19:37:19 2017 From: ghc-devs at haskell.org (GHC) Date: Thu, 08 Jun 2017 19:37:19 -0000 Subject: [GHC] #13756: Typo in user guide suggests that there's an -O* option In-Reply-To: <042.6a3b1c429314348df414591c312b566f@haskell.org> References: <042.6a3b1c429314348df414591c312b566f@haskell.org> Message-ID: <057.0cf3a363c0a3377b797f7077406557a1@haskell.org> #13756: Typo in user guide suggests that there's an -O* option -------------------------------------+------------------------------------- Reporter: nh2 | Owner: SantiM Type: bug | Status: closed Priority: normal | Milestone: 8.2.1 Component: Documentation | Version: 8.0.2 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3631 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => closed * resolution: => fixed -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jun 8 19:38:01 2017 From: ghc-devs at haskell.org (GHC) Date: Thu, 08 Jun 2017 19:38:01 -0000 Subject: [GHC] #13701: GHCi 2x slower without -keep-tmp-files In-Reply-To: <046.5313c8330fb56c9723008f1f4396a25a@haskell.org> References: <046.5313c8330fb56c9723008f1f4396a25a@haskell.org> Message-ID: <061.d65b1844d586294115d8e0cd1bc38a60@haskell.org> #13701: GHCi 2x slower without -keep-tmp-files -------------------------------------+------------------------------------- Reporter: niteria | Owner: duog Type: task | Status: closed Priority: normal | Milestone: 8.4.1 Component: GHCi | Version: 8.3 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3620 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: patch => closed * resolution: => fixed * milestone: => 8.4.1 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jun 8 19:50:42 2017 From: ghc-devs at haskell.org (GHC) Date: Thu, 08 Jun 2017 19:50:42 -0000 Subject: [GHC] #11501: Building nofib/fibon returns permission denied In-Reply-To: <042.7732253ef90810c7acc41907aecb19ff@haskell.org> References: <042.7732253ef90810c7acc41907aecb19ff@haskell.org> Message-ID: <057.2702e55219dba09f4cb3c7fd8c57f7b6@haskell.org> #11501: Building nofib/fibon returns permission denied -------------------------------------+------------------------------------- Reporter: rem | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.2.1 Component: NoFib benchmark | Version: 7.10.3 suite | Resolution: fixed | Keywords: Operating System: Linux | Architecture: x86_64 | (amd64) Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => closed * resolution: => fixed * milestone: => 8.2.1 Comment: Let's close is and open a new ticket for `nofib` improvements. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jun 8 19:53:30 2017 From: ghc-devs at haskell.org (GHC) Date: Thu, 08 Jun 2017 19:53:30 -0000 Subject: [GHC] #13802: Installation of yesod-auth-1.4.13.2 fails with "ghc: panic! (the 'impossible' happened)" In-Reply-To: <043.1f3d248765c4d66da4ba309745c7dadb@haskell.org> References: <043.1f3d248765c4d66da4ba309745c7dadb@haskell.org> Message-ID: <058.303728665234bd74d89351e99eb7f782@haskell.org> #13802: Installation of yesod-auth-1.4.13.2 fails with "ghc: panic! (the 'impossible' happened)" -------------------------------------+------------------------------------- Reporter: nvbt | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 8.0.2 Resolution: duplicate | Keywords: panic, stack, | install Operating System: MacOS X | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: #12479 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => closed * resolution: => duplicate * related: => #12479 Comment: This is a duplicate of #12479 and is fixed in GHC 8.0.2. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jun 8 19:54:35 2017 From: ghc-devs at haskell.org (GHC) Date: Thu, 08 Jun 2017 19:54:35 -0000 Subject: [GHC] #13707: xmobar crashes with segmentation faults? In-Reply-To: <046.fbf7af7bdea4e00dc6b71cd4d89ec01e@haskell.org> References: <046.fbf7af7bdea4e00dc6b71cd4d89ec01e@haskell.org> Message-ID: <061.86d76d494f36ba71c2afb630ad8a7c0d@haskell.org> #13707: xmobar crashes with segmentation faults? -------------------------------------+------------------------------------- Reporter: bgamari | Owner: (none) Type: bug | Status: infoneeded Priority: highest | Milestone: 8.2.1 Component: Compiler | Version: 8.2.1-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => infoneeded Comment: Hmm, alright. Sorry for the crashes. I would love to look at a core dump of your crashing executable (and perhaps the executable itself) if you get a chance. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jun 8 20:05:37 2017 From: ghc-devs at haskell.org (GHC) Date: Thu, 08 Jun 2017 20:05:37 -0000 Subject: [GHC] #13795: :kind! is not expanding type synonyms anymore In-Reply-To: <045.9bd0a404a46fb5b0930c49818b8cb45d@haskell.org> References: <045.9bd0a404a46fb5b0930c49818b8cb45d@haskell.org> Message-ID: <060.cb8d6e66f137fcddcbf81e0d5c18c99d@haskell.org> #13795: :kind! is not expanding type synonyms anymore -------------------------------------+------------------------------------- Reporter: Hjulle | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: GHCi | Version: 8.0.2 Resolution: | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by goldfire): IIRC, this was a deliberate choice: the idea was that type families are best understood after expansion but type synonyms are best understood without expanding. The process used in `:kind!` even looks through type synonyms to see if there are more type family reductions possible. This is all a matter of taste. We ''could'' change it (easily). Would it surprise other users? Perhaps. This is something wider community input might help to enlighten, but a full ghc-proposal seems rather heavy. I don't know of a lighter-weight way forward, though. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jun 8 20:12:09 2017 From: ghc-devs at haskell.org (GHC) Date: Thu, 08 Jun 2017 20:12:09 -0000 Subject: [GHC] #13803: Panic while forcing the thunk for TyThing IsFile (regression) In-Reply-To: <044.5fd6949417f66553983c80f17489c157@haskell.org> References: <044.5fd6949417f66553983c80f17489c157@haskell.org> Message-ID: <059.bda546a1c89bc8740f0aeeb8d9a941f1@haskell.org> #13803: Panic while forcing the thunk for TyThing IsFile (regression) -------------------------------------+------------------------------------- Reporter: inaki | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.1-rc2 Resolution: | Keywords: hs-boot Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): OK, here is as small as I can possibly make this: a "meager" five files: {{{#!hs -- D.hs {-# LANGUAGE TypeFamilies #-} module D (D) where type family D a type instance D Int = Int }}} {{{#!hs -- E.hs {-# LANGUAGE ConstraintKinds #-} {-# LANGUAGE TypeFamilies #-} module E where import GHC.Exts (Constraint) import {-# SOURCE #-} Y class C i where type CF i :: * -> Constraint data E instance C E where type CF E = Y }}} {{{#!hs -- E.hs-boot module E where }}} {{{#!hs -- Y.hs module Y where import D () import {-# SOURCE #-} E class Y o }}} {{{#!hs -- Y.hs-boot module Y where class Y o }}} {{{ $ /opt/ghc/8.2.1/bin/ghci Y.hs GHCi, version 8.2.0.20170522: http://www.haskell.org/ghc/ :? for help Loaded GHCi configuration from /home/rgscott/.ghci [1 of 5] Compiling D ( D.hs, interpreted ) [2 of 5] Compiling E[boot] ( E.hs-boot, interpreted ) [3 of 5] Compiling Y[boot] ( Y.hs-boot, interpreted ) [4 of 5] Compiling E ( E.hs, interpreted ) [5 of 5] Compiling Y ( Y.hs, interpreted ) ghc: panic! (the 'impossible' happened) (GHC version 8.2.0.20170522 for x86_64-unknown-linux): tcIfaceGlobal (local): not found You are in a maze of twisty little passages, all alike. While forcing the thunk for TyThing Y which was lazily initialized by initIfaceCheck typecheckLoop, I tried to tie the knot, but I couldn't find Y in the current type environment. If you are developing GHC, please read Note [Tying the knot] and Note [Type-checking inside the knot]. Consider rebuilding GHC with profiling for a better stack trace. Contents of current type environment: [] Call stack: CallStack (from HasCallStack): prettyCurrentCallStack, called at compiler/utils/Outputable.hs:1133:58 in ghc:Outputable callStackDoc, called at compiler/utils/Outputable.hs:1137:37 in ghc:Outputable pprPanic, called at compiler/iface/TcIface.hs:1689:23 in ghc:TcIface }}} Note that the name of `D.hs` actually matters here. For instance, if you rename `D.hs` to `Z.hs`, it'll actually compile! {{{ $ /opt/ghc/8.2.1/bin/ghci Y.hs GHCi, version 8.2.0.20170522: http://www.haskell.org/ghc/ :? for help Loaded GHCi configuration from /home/rgscott/.ghci [1 of 5] Compiling E[boot] ( E.hs-boot, interpreted ) [2 of 5] Compiling Y[boot] ( Y.hs-boot, interpreted ) [3 of 5] Compiling E ( E.hs, interpreted ) [4 of 5] Compiling Z ( Z.hs, interpreted ) [5 of 5] Compiling Y ( Y.hs, interpreted ) Ok, modules loaded: E, E, Y, Y, Z. }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jun 8 20:52:34 2017 From: ghc-devs at haskell.org (GHC) Date: Thu, 08 Jun 2017 20:52:34 -0000 Subject: [GHC] #13803: Panic while forcing the thunk for TyThing IsFile (regression) In-Reply-To: <044.5fd6949417f66553983c80f17489c157@haskell.org> References: <044.5fd6949417f66553983c80f17489c157@haskell.org> Message-ID: <059.b8bdd953263fc55451a03dcc8b31f920@haskell.org> #13803: Panic while forcing the thunk for TyThing IsFile (regression) -------------------------------------+------------------------------------- Reporter: inaki | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.1-rc2 Resolution: | Keywords: hs-boot Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * cc: ezyang (added) Comment: Edward is the expert here. I'm cc'ing him in the hope he can help. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jun 8 20:56:14 2017 From: ghc-devs at haskell.org (GHC) Date: Thu, 08 Jun 2017 20:56:14 -0000 Subject: [GHC] #13701: GHCi 2x slower without -keep-tmp-files In-Reply-To: <046.5313c8330fb56c9723008f1f4396a25a@haskell.org> References: <046.5313c8330fb56c9723008f1f4396a25a@haskell.org> Message-ID: <061.56a13213d90d1ebf8b23d5251073b44c@haskell.org> #13701: GHCi 2x slower without -keep-tmp-files -------------------------------------+------------------------------------- Reporter: niteria | Owner: duog Type: task | Status: closed Priority: normal | Milestone: 8.4.1 Component: GHCi | Version: 8.3 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: T13701 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3620 Wiki Page: | -------------------------------------+------------------------------------- Changes (by duog): * testcase: => T13701 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jun 8 21:48:58 2017 From: ghc-devs at haskell.org (GHC) Date: Thu, 08 Jun 2017 21:48:58 -0000 Subject: [GHC] #13795: :kind! is not expanding type synonyms anymore In-Reply-To: <045.9bd0a404a46fb5b0930c49818b8cb45d@haskell.org> References: <045.9bd0a404a46fb5b0930c49818b8cb45d@haskell.org> Message-ID: <060.6a01e7f003816a0896e9ef27a63b6cb2@haskell.org> #13795: :kind! is not expanding type synonyms anymore -------------------------------------+------------------------------------- Reporter: Hjulle | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: GHCi | Version: 8.0.2 Resolution: | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Hjulle): I found this when I was looking for a way to expand type signatures. According to https://stackoverflow.com/questions/13595773/expand-type- synonyms-type-families-with-ghci :kind! is the way to do it. If it was intentional to remove that, is there another way to expand type signatures in ghci? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jun 8 22:11:18 2017 From: ghc-devs at haskell.org (GHC) Date: Thu, 08 Jun 2017 22:11:18 -0000 Subject: [GHC] #13804: MonoLocalBinds/RankNTypes type inference regression in GHC 8.2 Message-ID: <050.b9855b85679e008576846333f1b379f9@haskell.org> #13804: MonoLocalBinds/RankNTypes type inference regression in GHC 8.2 -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: highest | Milestone: Component: Compiler | Version: 8.2.1-rc2 (Type checker) | Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: GHC rejects Unknown/Multiple | valid program Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- I encountered this problem when trying to compile the `ivory-bsp-stm32` library (unsuccessfully) with GHC 8.2. Here's a somewhat minimized example: {{{#!hs {-# LANGUAGE DataKinds #-} {-# LANGUAGE ExistentialQuantification #-} {-# LANGUAGE KindSignatures #-} -- Not enabling MonoLocalBinds makes it compile again {-# LANGUAGE MonoLocalBinds #-} {-# LANGUAGE RankNTypes #-} module Bug where import GHC.TypeLits i2cPeripheralDriver :: I2CPeriph -> ChanOutput ('Stored ITime) -> Monitor e () i2cPeripheralDriver periph watchdog_per = do let sendresult' :: Ivory eff () sendresult' = do -- Commenting out the line below makes it compile again clearSR1 periph return undefined sendresult = sendresult' handler watchdog_per undefined $ do callback $ \_ -> do sendresult return undefined clearSR1 :: I2CPeriph -> Ivory eff () clearSR1 = undefined ----- -- Auxiliary definitions ----- data ITime data I2CPeriph = I2CPeriph data Ivory (eff :: Effects) a instance Functor (Ivory eff) instance Applicative (Ivory eff) instance Monad (Ivory eff) data Monitor e a instance Functor (Monitor e) instance Applicative (Monitor e) instance Monad (Monitor e) data ChanOutput (a :: Area *) data RefScope = Global | forall s. Stack s type ConstRef = Pointer 'Valid 'Const -- :: RefScope -> Area * -> * data Nullability = Nullable | Valid data Constancy = Const | Mutable data Pointer (n :: Nullability) (c :: Constancy) (s :: RefScope) (a :: Area *) type AllocEffects s = 'Effects 'NoReturn 'NoBreak ('Scope s) -- :: Effects data Effects = Effects ReturnEff BreakEff AllocEff data ReturnEff = forall t. Returns t | NoReturn data BreakEff = Break | NoBreak data AllocEff = forall s. Scope s | NoAlloc callback :: (IvoryArea a, IvoryZero a) => (forall (s :: RefScope) s'. ConstRef s a -> Ivory (AllocEffects s') ()) -> Handler a e () callback _ = undefined handler :: (IvoryArea a, IvoryZero a) => ChanOutput a -> String -> Handler a e () -> Monitor e () data Handler (area :: Area *) e a handler = undefined data Area k = Struct Symbol | Array Nat (Area k) | CArray (Area k) | Stored k data Time class IvoryArea (a :: Area *) class IvoryZero (area :: Area *) where class IvoryType t instance IvoryType ITime instance IvoryType a => IvoryArea ('Stored a) class IvoryZeroVal a instance IvoryZeroVal ITime instance IvoryZeroVal a => IvoryZero ('Stored a) }}} In GHC 7.10 and 8.0, this compiles. With GHC 8.2, however, it errors: {{{#!hs GHCi, version 8.2.0.20170522: http://www.haskell.org/ghc/ :? for help Loaded GHCi configuration from /home/rgscott/.ghci [1 of 1] Compiling Bug ( Bug.hs, interpreted ) Bug.hs:25:7: error: • Couldn't match type ‘eff0’ with ‘AllocEffects s'’ because type variable ‘s'’ would escape its scope This (rigid, skolem) type variable is bound by a type expected by the context: forall (s :: RefScope) s'. ConstRef s ('Stored ITime) -> Ivory (AllocEffects s') () at Bug.hs:(24,5)-(25,16) Expected type: Ivory (AllocEffects s') () Actual type: Ivory eff0 () • In a stmt of a 'do' block: sendresult In the expression: do sendresult In the second argument of ‘($)’, namely ‘\ _ -> do sendresult’ • Relevant bindings include sendresult :: Ivory eff0 () (bound at Bug.hs:21:7) | 25 | sendresult | ^^^^^^^^^^ }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jun 8 22:11:45 2017 From: ghc-devs at haskell.org (GHC) Date: Thu, 08 Jun 2017 22:11:45 -0000 Subject: [GHC] #13804: MonoLocalBinds/RankNTypes type inference regression in GHC 8.2 In-Reply-To: <050.b9855b85679e008576846333f1b379f9@haskell.org> References: <050.b9855b85679e008576846333f1b379f9@haskell.org> Message-ID: <065.817e0620c13cd34b96eb6c0440e5a690@haskell.org> #13804: MonoLocalBinds/RankNTypes type inference regression in GHC 8.2 -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: highest | Milestone: Component: Compiler (Type | Version: 8.2.1-rc2 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Description changed by RyanGlScott: @@ -122,1 +122,1 @@ - {{{#!hs + {{{ New description: I encountered this problem when trying to compile the `ivory-bsp-stm32` library (unsuccessfully) with GHC 8.2. Here's a somewhat minimized example: {{{#!hs {-# LANGUAGE DataKinds #-} {-# LANGUAGE ExistentialQuantification #-} {-# LANGUAGE KindSignatures #-} -- Not enabling MonoLocalBinds makes it compile again {-# LANGUAGE MonoLocalBinds #-} {-# LANGUAGE RankNTypes #-} module Bug where import GHC.TypeLits i2cPeripheralDriver :: I2CPeriph -> ChanOutput ('Stored ITime) -> Monitor e () i2cPeripheralDriver periph watchdog_per = do let sendresult' :: Ivory eff () sendresult' = do -- Commenting out the line below makes it compile again clearSR1 periph return undefined sendresult = sendresult' handler watchdog_per undefined $ do callback $ \_ -> do sendresult return undefined clearSR1 :: I2CPeriph -> Ivory eff () clearSR1 = undefined ----- -- Auxiliary definitions ----- data ITime data I2CPeriph = I2CPeriph data Ivory (eff :: Effects) a instance Functor (Ivory eff) instance Applicative (Ivory eff) instance Monad (Ivory eff) data Monitor e a instance Functor (Monitor e) instance Applicative (Monitor e) instance Monad (Monitor e) data ChanOutput (a :: Area *) data RefScope = Global | forall s. Stack s type ConstRef = Pointer 'Valid 'Const -- :: RefScope -> Area * -> * data Nullability = Nullable | Valid data Constancy = Const | Mutable data Pointer (n :: Nullability) (c :: Constancy) (s :: RefScope) (a :: Area *) type AllocEffects s = 'Effects 'NoReturn 'NoBreak ('Scope s) -- :: Effects data Effects = Effects ReturnEff BreakEff AllocEff data ReturnEff = forall t. Returns t | NoReturn data BreakEff = Break | NoBreak data AllocEff = forall s. Scope s | NoAlloc callback :: (IvoryArea a, IvoryZero a) => (forall (s :: RefScope) s'. ConstRef s a -> Ivory (AllocEffects s') ()) -> Handler a e () callback _ = undefined handler :: (IvoryArea a, IvoryZero a) => ChanOutput a -> String -> Handler a e () -> Monitor e () data Handler (area :: Area *) e a handler = undefined data Area k = Struct Symbol | Array Nat (Area k) | CArray (Area k) | Stored k data Time class IvoryArea (a :: Area *) class IvoryZero (area :: Area *) where class IvoryType t instance IvoryType ITime instance IvoryType a => IvoryArea ('Stored a) class IvoryZeroVal a instance IvoryZeroVal ITime instance IvoryZeroVal a => IvoryZero ('Stored a) }}} In GHC 7.10 and 8.0, this compiles. With GHC 8.2, however, it errors: {{{ GHCi, version 8.2.0.20170522: http://www.haskell.org/ghc/ :? for help Loaded GHCi configuration from /home/rgscott/.ghci [1 of 1] Compiling Bug ( Bug.hs, interpreted ) Bug.hs:25:7: error: • Couldn't match type ‘eff0’ with ‘AllocEffects s'’ because type variable ‘s'’ would escape its scope This (rigid, skolem) type variable is bound by a type expected by the context: forall (s :: RefScope) s'. ConstRef s ('Stored ITime) -> Ivory (AllocEffects s') () at Bug.hs:(24,5)-(25,16) Expected type: Ivory (AllocEffects s') () Actual type: Ivory eff0 () • In a stmt of a 'do' block: sendresult In the expression: do sendresult In the second argument of ‘($)’, namely ‘\ _ -> do sendresult’ • Relevant bindings include sendresult :: Ivory eff0 () (bound at Bug.hs:21:7) | 25 | sendresult | ^^^^^^^^^^ }}} -- -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jun 8 22:14:16 2017 From: ghc-devs at haskell.org (GHC) Date: Thu, 08 Jun 2017 22:14:16 -0000 Subject: [GHC] #13800: ghc panic: No skolem info: s_a7aK[sk] In-Reply-To: <043.5dfb097ffcc0e2a2a2d4ef00d5efca40@haskell.org> References: <043.5dfb097ffcc0e2a2a2d4ef00d5efca40@haskell.org> Message-ID: <058.9b68bdc5114379936995f09f6c065857@haskell.org> #13800: ghc panic: No skolem info: s_a7aK[sk] -------------------------------------+------------------------------------- Reporter: hexo | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: x86_64 Type of failure: Compile-time | (amd64) crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): I tried to build the library with GHC 8.2, but unfortunately, I was unable to compile a dependency (`ivory-bsp-stm32`) due to a GHC 8.2 regression. See #13804. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 9 00:03:57 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 09 Jun 2017 00:03:57 -0000 Subject: [GHC] #8809: Prettier error messages? In-Reply-To: <047.4dbdad421fcd945584d210433034ccb5@haskell.org> References: <047.4dbdad421fcd945584d210433034ccb5@haskell.org> Message-ID: <062.36a2c3034031e6bbdc45e90aab81da99@haskell.org> #8809: Prettier error messages? -------------------------------------+------------------------------------- Reporter: joelteon | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.9 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: 13122 Related Tickets: | Differential Rev(s): #8809,#10073,#10179,#12906,#13670 | Wiki Page: | -------------------------------------+------------------------------------- Comment (by gracjan): I'd like to put aside issue of colors and technology used and focus on two things 1) the copy, the text used 2) error message structure. Personally, my list of gripes with Haskell error message text is as follows: 1. Lack of googleable error message title. 2. GHC should better quote code verbatim instead of pretty-printing AST. 3. GHC tries to name things instead of pointing me to things. I need to find them anyway to get errors fixed. 4. Location info is sometimes on the right. Therefore I'd like to propose a list of tenets for error message copy: 1. First line is a googleable (i.e. preferably not interpolated), single line stating the problem 2. GHC should point to things instead of naming them. 3. GHC should pretty-print only synthesized information (e.g. type inference generated types), otherwise it should point to code 4. Adopt MS VisualStudio standard to point to relevant information, i. e. "note:" messages. 5. GHC quotes at most 1 line of source code, cutting output at end of line. In practice, current message about type families: {{{ T10836.hs:5:5: error: Type family equations violate injectivity annotation: Foo Int = Int -- Defined at T10836.hs:5:5 Foo Bool = Int -- Defined at T10836.hs:6:5 In the equations for closed type family ‘Foo’ In the type family declaration for ‘Foo’ }}} I'd like to analyze the above a bit. It has a googleable title, this is good, but the information from last two lines should be moved up. Identifier 'Foo' appears 4 times here, it is probably important. Location info is on the right, tools like editors have problems finding it and providing easy navigation, and GHC is not consistent with formatting of relevant file:line:col pointers. I'd like to propose redacting the above to (full version): {{{ T10836.hs:5:5: error: Closed type family equations violate injectivity annotation: Foo {-# PRAGMA #-} Int = Int ^~~ T10836.hs:6:5: note: other violating declaration Foo Bool = Int -- TODO: joe: remove by March ^~~ }}} And embedded (editor, non-quoting) version: {{{ T10836.hs:5:5: error: Closed type family equations violate injectivity annotation: T10836.hs:6:5: note: other violating declaration }}} Again, analysing: 1. A googleable header: yes. 2. Pointing to things instead of naming them: yes. 3. Quoting source code verbatim: yes. A to answer goldfire quesion "[This modified version] is much easier to visually process than GHC's current messages." from comment:2, from years before, this version is better because: 1. Structure of message is more rigid and enables better pattern matching by a human eye and by a navigating editor. 2. Quoting source code verbatim enables faster visual matching between error report and source code. 3. Concise title enables googling for answers. 4. Pointing to instead of naming removes a layer of indirection that needs to be followed by a human should s/he be fixing the issue in the code. Having said that I do not mind colors provided they are in predictable places (I mean, it is nice that "warning" and "error" are always pink but I would be weary introducing color mid-sentence in the message itself). I have also the feeling that my proposal "point to instead of naming" in reality requires only LINE:COL annotations in SDoc. At least I do not really see a useful annotation of any other type. While working on haskell-mode (for Emacs) I've found error spans of limited use. Indeed, given error message + pointing to first char usually is enough for a human to know if error message talks about identifier starting here or expression starting here or declaration starting here. I've done some more thinking here: https://ghc.haskell.org/trac/ghc/wiki/Proposal/ErrorMessages -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 9 00:12:44 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 09 Jun 2017 00:12:44 -0000 Subject: [GHC] #13805: GHC 8.0.2 fails to build on macOS 10.13/Xcode 9 - preprocessor error in ghc-pkg Message-ID: <049.5c553f223a194e22fdf785f7cd8ea0f5@haskell.org> #13805: GHC 8.0.2 fails to build on macOS 10.13/Xcode 9 - preprocessor error in ghc-pkg -------------------------------------+------------------------------------- Reporter: mistydemeo | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: ghc-pkg | Version: 8.0.2 Keywords: | Operating System: MacOS X Architecture: x86_64 | Type of failure: Building GHC (amd64) | failed Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- Building GHC 8.0.2 on macOS 10.13 fails with the following error when building {{{ utils/ghc-pkg/Main.hs:1269:40: error: error: editor placeholder in source file then termText (location db) <#> termText "\n (no packages)\n" ^ }}} I'm not very familiar with Haskell, but it looks to me like the C preprocessor is mistaking `<#>` for an invalid cpp directive instead of Haskell syntax. This is using the Xcode 9 beta (and its associated CLT), which ships "Apple LLVM version 9.0.0 (clang-900.0.22.8)". The same version should be available in the Xcode 9 beta for 10.12, but I haven't tested. The full build logs are available here: https://gist.github.com/anonymous/dc5f0c9d087f5d299f71393805c5d611 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 9 01:47:55 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 09 Jun 2017 01:47:55 -0000 Subject: [GHC] #13806: Invalid usage of TypeFamilies cause GHC Internal Error Message-ID: <046.8812a8f391082657aadee30e16d1746e@haskell.org> #13806: Invalid usage of TypeFamilies cause GHC Internal Error -------------------------------------+------------------------------------- Reporter: utdemir | Owner: (none) Type: bug | Status: new Priority: low | Milestone: Component: Compiler | Version: 8.0.2 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: Incorrect Unknown/Multiple | error/warning at compile-time Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- I couldn't be able to reproduce this with a valid program, but seeing "GHC internal error" was surprising. Only the second error should be enough in this case. {{{ $ cat test.hs {-# LANGUAGE TypeFamilies #-} data Foo value = Foo (T value) class Cl t where type T mk :: t -> T main :: IO () main = undefined $ runhaskell test.hs test.hs:4:10: error: • GHC internal error: ‘T’ is not in scope during type checking, but it passed the renamer tcl_env of environment: [a10K :-> Type variable ‘value’ = value, r10F :-> ATcTyCon Foo, r10G :-> APromotionErr RecDataConPE] • In the type ‘T value’ In the definition of data constructor ‘Foo’ In the data declaration for ‘Foo’ test.hs:6:1: error: • The associated type ‘T’ mentions none of the type or kind variables of the class ‘Cl t’ • In the class declaration for ‘Cl’ $ runhaskell --version runghc 8.0.2 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 9 01:49:00 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 09 Jun 2017 01:49:00 -0000 Subject: [GHC] #13806: Invalid usage of TypeFamilies cause GHC Internal Error In-Reply-To: <046.8812a8f391082657aadee30e16d1746e@haskell.org> References: <046.8812a8f391082657aadee30e16d1746e@haskell.org> Message-ID: <061.004bbedc92fe3cb71d8b08b0b6d1511c@haskell.org> #13806: Invalid usage of TypeFamilies cause GHC Internal Error -------------------------------------+------------------------------------- Reporter: utdemir | Owner: (none) Type: bug | Status: new Priority: low | Milestone: Component: Compiler | Version: 8.0.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple error/warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Description changed by utdemir: @@ -1,3 +1,3 @@ - I couldn't be able to reproduce this with a valid program, but seeing "GHC - internal error" was surprising. Only the second error should be enough in - this case. + I couldn't be able to reproduce this with a valid program, but even on an + invalid program seeing "GHC internal error" is unexpected. Only the second + error should be enough in this case. New description: I couldn't be able to reproduce this with a valid program, but even on an invalid program seeing "GHC internal error" is unexpected. Only the second error should be enough in this case. {{{ $ cat test.hs {-# LANGUAGE TypeFamilies #-} data Foo value = Foo (T value) class Cl t where type T mk :: t -> T main :: IO () main = undefined $ runhaskell test.hs test.hs:4:10: error: • GHC internal error: ‘T’ is not in scope during type checking, but it passed the renamer tcl_env of environment: [a10K :-> Type variable ‘value’ = value, r10F :-> ATcTyCon Foo, r10G :-> APromotionErr RecDataConPE] • In the type ‘T value’ In the definition of data constructor ‘Foo’ In the data declaration for ‘Foo’ test.hs:6:1: error: • The associated type ‘T’ mentions none of the type or kind variables of the class ‘Cl t’ • In the class declaration for ‘Cl’ $ runhaskell --version runghc 8.0.2 }}} -- -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 9 02:20:12 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 09 Jun 2017 02:20:12 -0000 Subject: [GHC] #13806: Invalid usage of TypeFamilies cause GHC Internal Error In-Reply-To: <046.8812a8f391082657aadee30e16d1746e@haskell.org> References: <046.8812a8f391082657aadee30e16d1746e@haskell.org> Message-ID: <061.abb931aa37def39ae5451a52857bb7b4@haskell.org> #13806: Invalid usage of TypeFamilies cause GHC Internal Error -------------------------------------+------------------------------------- Reporter: utdemir | Owner: (none) Type: bug | Status: closed Priority: low | Milestone: Component: Compiler | Version: 8.0.2 Resolution: duplicate | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple error/warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: #12867 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * status: new => closed * resolution: => duplicate * related: => #12867 Comment: Thanks for the bug report. This is a duplicate of #12867, which has been fixed in GHC 8.2.1. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 9 03:01:35 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 09 Jun 2017 03:01:35 -0000 Subject: [GHC] #13804: MonoLocalBinds/RankNTypes type inference regression in GHC 8.2 In-Reply-To: <050.b9855b85679e008576846333f1b379f9@haskell.org> References: <050.b9855b85679e008576846333f1b379f9@haskell.org> Message-ID: <065.dfbfd67c9c98a343d14cc66c6a6098b4@haskell.org> #13804: MonoLocalBinds/RankNTypes type inference regression in GHC 8.2 -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: highest | Milestone: Component: Compiler (Type | Version: 8.2.1-rc2 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: #11698 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * cc: facundo.dominguez (added) * related: => #11698 Comment: This behavior was introduced in commit c9e8f801170b213b85735ed403f24b2842aedf1b (Set tct_closed to TopLevel for closed bindings). Facundo, is this expected? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 9 03:31:00 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 09 Jun 2017 03:31:00 -0000 Subject: [GHC] #13800: ghc panic: No skolem info: s_a7aK[sk] In-Reply-To: <043.5dfb097ffcc0e2a2a2d4ef00d5efca40@haskell.org> References: <043.5dfb097ffcc0e2a2a2d4ef00d5efca40@haskell.org> Message-ID: <058.3ef28044fc573aedb54fb89e02fc50f3@haskell.org> #13800: ghc panic: No skolem info: s_a7aK[sk] -------------------------------------+------------------------------------- Reporter: hexo | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 8.0.2 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: x86_64 Type of failure: Compile-time | (amd64) crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * status: new => closed * resolution: => fixed Comment: OK, I was able to work around #13804 by adding `{-# LANGUAGE NoMonoLocalBinds #-}` to the appropriate file in `ivory-bsp-stm32`. I was then able to build `clock` (and run `blink-test`) without any issues on GHC 8.2. I think this is as good of a confirmation as we're going to get that the issue experienced here has been fixed, so I'll close this ticket. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 9 03:45:39 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 09 Jun 2017 03:45:39 -0000 Subject: [GHC] #13803: Panic while forcing the thunk for TyThing IsFile (regression) In-Reply-To: <044.5fd6949417f66553983c80f17489c157@haskell.org> References: <044.5fd6949417f66553983c80f17489c157@haskell.org> Message-ID: <059.b3780367edbded5ee1447f07f0f131d0@haskell.org> #13803: Panic while forcing the thunk for TyThing IsFile (regression) -------------------------------------+------------------------------------- Reporter: inaki | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.1-rc2 Resolution: | Keywords: hs-boot Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by ezyang): This is a family instance consistency check problem, as can be seen when you turn on tracing: {{{ checkForConflictsghc-stage2: panic! (the 'impossible' happened) (GHC version 8.3.20170517 for x86_64-unknown-linux): tcIfaceGlobal (local): not found }}} We begin checking for conflicts immediately before the panic. The problem is reminiscent of #11062 (fixed in 25b70a29f6236b591252bf5a361a1547f0ffee51). -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 9 03:52:15 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 09 Jun 2017 03:52:15 -0000 Subject: [GHC] #12545: Compilation time/space regression in GHC 8.0/8.1 (search in type-level lists and -O) In-Reply-To: <057.9aecaec89b7fd255565e55bac0801cc6@haskell.org> References: <057.9aecaec89b7fd255565e55bac0801cc6@haskell.org> Message-ID: <072.1925adfce8a16509927e68b6be46b4b6@haskell.org> #12545: Compilation time/space regression in GHC 8.0/8.1 (search in type-level lists and -O) -------------------------------------+------------------------------------- Reporter: | Owner: (none) mikhail.vorozhtsov | Type: bug | Status: patch Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Inlining Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3632 Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * status: new => patch * differential: => Phab:D3632 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 9 04:28:48 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 09 Jun 2017 04:28:48 -0000 Subject: [GHC] #13803: Panic while forcing the thunk for TyThing IsFile (regression) In-Reply-To: <044.5fd6949417f66553983c80f17489c157@haskell.org> References: <044.5fd6949417f66553983c80f17489c157@haskell.org> Message-ID: <059.cf5bb942b64275de8d14082e7257959e@haskell.org> #13803: Panic while forcing the thunk for TyThing IsFile (regression) -------------------------------------+------------------------------------- Reporter: inaki | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.1-rc2 Resolution: | Keywords: hs-boot Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by ezyang): This appears to fix the problem but we may need to figure out something more efficient, since adding the forkM here affects ALL axioms we load from interfaces. {{{ diff --git a/compiler/iface/TcIface.hs b/compiler/iface/TcIface.hs index 3a6a4070d2..0fad1da50b 100644 --- a/compiler/iface/TcIface.hs +++ b/compiler/iface/TcIface.hs @@ -807,7 +807,7 @@ tc_iface_decl _parent ignore_prags tc_iface_decl _ _ (IfaceAxiom { ifName = tc_name, ifTyCon = tc , ifAxBranches = branches, ifRole = role }) = do { tc_tycon <- tcIfaceTyCon tc - ; tc_branches <- tc_ax_branches branches + ; tc_branches <- forkM (text "Axiom branches" <+> ppr tc_name) $ tc_ax_branches branches ; let axiom = CoAxiom { co_ax_unique = nameUnique tc_name , co_ax_name = tc_name , co_ax_tc = tc_tycon }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 9 07:56:51 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 09 Jun 2017 07:56:51 -0000 Subject: [GHC] #13795: :kind! is not expanding type synonyms anymore In-Reply-To: <045.9bd0a404a46fb5b0930c49818b8cb45d@haskell.org> References: <045.9bd0a404a46fb5b0930c49818b8cb45d@haskell.org> Message-ID: <060.f8c7da1289255b65d7912a1738005b26@haskell.org> #13795: :kind! is not expanding type synonyms anymore -------------------------------------+------------------------------------- Reporter: Hjulle | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: GHCi | Version: 8.0.2 Resolution: | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): We could offer some way to get * No processing of the type (currently `:kind`) * Type families evaluated (currently `:kind!`) * Type families evaluated and type synonyms expanded (`:kind!!` perhaps?) And, I suppose, the fourth possibility (expand type synonyms but do not evaluate type families). But that's probably over-complicated -- few users would care. If we are going to have only two possibilities (`:k` and `:k!`), what the user manual says makes most sense: `:kind!` evaluates everything, type families, type synonyms and all. I suppose we could have a `:set -XNoExpandSynonymsOnBang` flag or something. Implementation is easy. The hard thing to know is what users want. Users, speak up! -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 9 07:59:30 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 09 Jun 2017 07:59:30 -0000 Subject: [GHC] #13803: Panic while forcing the thunk for TyThing IsFile (regression) In-Reply-To: <044.5fd6949417f66553983c80f17489c157@haskell.org> References: <044.5fd6949417f66553983c80f17489c157@haskell.org> Message-ID: <059.fd0b8dbb3ccd29e972e214e5121c4f03@haskell.org> #13803: Panic while forcing the thunk for TyThing IsFile (regression) -------------------------------------+------------------------------------- Reporter: inaki | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.1-rc2 Resolution: | Keywords: hs-boot Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): It also means that less work is done (and perhaps even fewer interface files read, which is big) if the axiom is never actually needed. So it might be ''more'' efficient. Not reading interface files too eagerly is one of the original reasons for the whole `forkM` story in `TcIface`. Would you like to try? Please comment the change, with a reference to this ticket. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 9 09:57:38 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 09 Jun 2017 09:57:38 -0000 Subject: [GHC] #9374: Investigate Static Argument Transformation In-Reply-To: <048.23fff567ef50b1dc01dc4be619333c72@haskell.org> References: <048.23fff567ef50b1dc01dc4be619333c72@haskell.org> Message-ID: <063.9124aac57594c75c74837408a8f26e98@haskell.org> #9374: Investigate Static Argument Transformation -------------------------------------+------------------------------------- Reporter: jstolarek | Owner: (none) Type: task | Status: new Priority: lowest | Milestone: Component: Compiler | Version: 7.9 Resolution: | Keywords: | StaticArgumentTransformation Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * cc: kavon (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 9 10:07:06 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 09 Jun 2017 10:07:06 -0000 Subject: [GHC] #9476: Implement late lambda-lifting In-Reply-To: <046.35548079b7f5bfa7d29f786dd2f07078@haskell.org> References: <046.35548079b7f5bfa7d29f786dd2f07078@haskell.org> Message-ID: <061.17c3bcd03aef038f0107417a34e9ff2d@haskell.org> #9476: Implement late lambda-lifting -------------------------------------+------------------------------------- Reporter: simonpj | Owner: nfrisby Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.8.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: LateLamLift | -------------------------------------+------------------------------------- Changes (by simonpj): * cc: kavon (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 9 10:18:27 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 09 Jun 2017 10:18:27 -0000 Subject: [GHC] #13807: GHC 8.2 nondeterministic with foreign imports Message-ID: <046.b74945b333405c65044cabd09b1ff21f@haskell.org> #13807: GHC 8.2 nondeterministic with foreign imports -------------------------------------+------------------------------------- Reporter: niteria | Owner: (none) Type: bug | Status: new Priority: high | Milestone: Component: Compiler | Version: 8.2.1-rc2 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- See the attached Repro.hs. Reproduction steps: {{{ $ rm Repro.{o,hi}; ghc -O -dunique-increment=-1 Repro.hs; md5sum Repro.hi; rm Repro.{o,hi}; ghc -O -dunique-increment=1 Repro.hs; md5sum Repro.hi; [1 of 1] Compiling Repro ( Repro.hs, Repro.o ) 97f005e3959b657bfac761aa3e8a9447 Repro.hi [1 of 1] Compiling Repro ( Repro.hs, Repro.o ) 691f891fb404eb874e8bedd7bda1c8b7 Repro.hi }}} The crucial difference comes from: {{{ 08fffd1551f79b5aca3cafdceaf865b9 mkStringWriter1 :: Int -> State# RealWorld -> (# State# RealWorld, Ptr Int #) {- Arity: 2, HasNoCafRefs, Strictness: , Unfolding: InlineRule (2, True, False) (\ (ds :: Int) (s :: State# RealWorld) -> case makeStablePtr# @ Int ds s of ds1 { (#,#) ipv ipv1 -> case {__pkg_ccall Int# -> StablePtr# Int -> Addr# -> Addr# -> State# RealWorld -> (# State# RealWorld, Addr# #)} 1# ipv1 __label "Repro_d105" (function) mkStringWriter2 ipv of wild { (#,#) ds2 ds3 -> (# ds2, Ptr @ Int ds3 #) } }) -} }}} vs {{{ a766a748e60cec63a74534e03db3bf30 mkStringWriter1 :: Int -> State# RealWorld -> (# State# RealWorld, Ptr Int #) {- Arity: 2, HasNoCafRefs, Strictness: , Unfolding: InlineRule (2, True, False) (\ (ds :: Int) (s :: State# RealWorld) -> case makeStablePtr# @ Int ds s of ds1 { (#,#) ipv ipv1 -> case {__pkg_ccall Int# -> StablePtr# Int -> Addr# -> Addr# -> State# RealWorld -> (# State# RealWorld, Addr# #)} 1# ipv1 __label "Repro_d5k1wlNFGaX" (function) mkStringWriter2 ipv of wild { (#,#) ds2 ds3 -> (# ds2, Ptr @ Int ds3 #) } }) -} }}} Notice that the labels are different. This doesn't reproduce under GHC 8.0.2, but that may be only because that version doesn't optimize it this way. This is what GHC 8.0.2 produces: {{{ ccf55489bd76322a9404b365b7be7628 mkStringWriter :: Int -> IO (Ptr Int) {- Arity: 2, HasNoCafRefs, Strictness: , Inline: [NEVER] -} }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 9 10:19:12 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 09 Jun 2017 10:19:12 -0000 Subject: [GHC] #13807: GHC 8.2 nondeterministic with foreign imports In-Reply-To: <046.b74945b333405c65044cabd09b1ff21f@haskell.org> References: <046.b74945b333405c65044cabd09b1ff21f@haskell.org> Message-ID: <061.985c013a6ea5891de46a4129bf5ef6e1@haskell.org> #13807: GHC 8.2 nondeterministic with foreign imports -------------------------------------+------------------------------------- Reporter: niteria | Owner: (none) Type: bug | Status: new Priority: high | Milestone: Component: Compiler | Version: 8.2.1-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by niteria): * Attachment "Repro.hs" added. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 9 10:19:39 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 09 Jun 2017 10:19:39 -0000 Subject: [GHC] #13807: GHC 8.2 nondeterministic with foreign imports In-Reply-To: <046.b74945b333405c65044cabd09b1ff21f@haskell.org> References: <046.b74945b333405c65044cabd09b1ff21f@haskell.org> Message-ID: <061.773a0e79d91cd494359955818e293250@haskell.org> #13807: GHC 8.2 nondeterministic with foreign imports -------------------------------------+------------------------------------- Reporter: niteria | Owner: niteria Type: bug | Status: new Priority: high | Milestone: Component: Compiler | Version: 8.2.1-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by niteria): * owner: (none) => niteria -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 9 10:25:51 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 09 Jun 2017 10:25:51 -0000 Subject: [GHC] #13807: GHC 8.2 nondeterministic with foreign imports In-Reply-To: <046.b74945b333405c65044cabd09b1ff21f@haskell.org> References: <046.b74945b333405c65044cabd09b1ff21f@haskell.org> Message-ID: <061.09bdd1978463f50ec5436242fbd6a81f@haskell.org> #13807: GHC 8.2 nondeterministic with foreign imports -------------------------------------+------------------------------------- Reporter: niteria | Owner: niteria Type: bug | Status: new Priority: high | Milestone: Component: Compiler | Version: 8.2.1-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by niteria): This reproduces on GHC HEAD as well. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 9 12:40:51 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 09 Jun 2017 12:40:51 -0000 Subject: [GHC] #13807: GHC 8.2 nondeterministic with foreign imports In-Reply-To: <046.b74945b333405c65044cabd09b1ff21f@haskell.org> References: <046.b74945b333405c65044cabd09b1ff21f@haskell.org> Message-ID: <061.b51ef2672c39e892050d3480c60f08d3@haskell.org> #13807: GHC 8.2 nondeterministic with foreign imports -------------------------------------+------------------------------------- Reporter: niteria | Owner: niteria Type: bug | Status: new Priority: high | Milestone: Component: Compiler | Version: 8.2.1-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by niteria): I don't think this is a regression, the code that creates these labels is quite old: https://phabricator.haskell.org/diffusion/GHC/browse/master/compiler/deSugar/DsForeign.hs;b2b416014e4276ebb660d85c3a612f7ca45ade78$423 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 9 13:39:14 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 09 Jun 2017 13:39:14 -0000 Subject: [GHC] #13804: MonoLocalBinds/RankNTypes type inference regression in GHC 8.2 In-Reply-To: <050.b9855b85679e008576846333f1b379f9@haskell.org> References: <050.b9855b85679e008576846333f1b379f9@haskell.org> Message-ID: <065.70b1d1e79ac5fdd4b52b80f358f0116a@haskell.org> #13804: MonoLocalBinds/RankNTypes type inference regression in GHC 8.2 -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: highest | Milestone: Component: Compiler (Type | Version: 8.2.1-rc2 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: #11698 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by facundo.dominguez): Something odd is going on. Adding the type signature {{{sendresult :: Ivory eff ()}}} also makes the program compile. {{{tct_closed}}} is affected by the use of {{{periph}}} in {{{sendresult'}}}. This makes {{{sendresult}}} not closed. But I do not understand how this relates to the error message that GHC produces. It might be that some use of {{{tct_closed}}} in the type-checker is assuming its old meaning. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 9 14:19:09 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 09 Jun 2017 14:19:09 -0000 Subject: [GHC] #13691: Bump time submodule In-Reply-To: <046.7033f0ecc0a7c3600b088ca823c99a67@haskell.org> References: <046.7033f0ecc0a7c3600b088ca823c99a67@haskell.org> Message-ID: <061.187b5743aaaee489521d05b244d56b37@haskell.org> #13691: Bump time submodule -------------------------------------+------------------------------------- Reporter: bgamari | Owner: (none) Type: task | Status: new Priority: highest | Milestone: 8.2.1 Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by SantiM): Is this still a problem? AFAIK the current version (d03429e...) seems to build just fine for me. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 9 14:24:14 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 09 Jun 2017 14:24:14 -0000 Subject: [GHC] #13808: Bump Cabal submodule Message-ID: <046.c4d8d53c6ca66b8eb549fabfe34bf347@haskell.org> #13808: Bump Cabal submodule -------------------------------------+------------------------------------- Reporter: bgamari | Owner: (none) Type: bug | Status: new Priority: highest | Milestone: 8.2.1 Component: Compiler | Version: 8.2.1-rc2 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- Cabal 2.0.0.1 will be released shortly -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 9 15:46:55 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 09 Jun 2017 15:46:55 -0000 Subject: [GHC] #12390: List rules for `Coercible` instances In-Reply-To: <051.b98e23ec385e9c48fab8abae2b183162@haskell.org> References: <051.b98e23ec385e9c48fab8abae2b183162@haskell.org> Message-ID: <066.e6ea55d2a65ec0255f55e86877ed1b54@haskell.org> #12390: List rules for `Coercible` instances -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: bug | Status: patch Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: ghci059 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3634 Wiki Page: | -------------------------------------+------------------------------------- Changes (by tellah): * testcase: => ghci059 * status: new => patch * differential: => Phab:D3634 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 9 15:47:24 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 09 Jun 2017 15:47:24 -0000 Subject: [GHC] #12390: List rules for `Coercible` instances In-Reply-To: <051.b98e23ec385e9c48fab8abae2b183162@haskell.org> References: <051.b98e23ec385e9c48fab8abae2b183162@haskell.org> Message-ID: <066.dbe15d53b317c7a6821ae33d3c14f6b4@haskell.org> #12390: List rules for `Coercible` instances -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: tellah Type: bug | Status: patch Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: ghci059 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3634 Wiki Page: | -------------------------------------+------------------------------------- Changes (by tellah): * owner: (none) => tellah -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 9 16:07:38 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 09 Jun 2017 16:07:38 -0000 Subject: [GHC] #8809: Prettier error messages? In-Reply-To: <047.4dbdad421fcd945584d210433034ccb5@haskell.org> References: <047.4dbdad421fcd945584d210433034ccb5@haskell.org> Message-ID: <062.d8a9ec104ee12837efa9d3ea885ad760@haskell.org> #8809: Prettier error messages? -------------------------------------+------------------------------------- Reporter: joelteon | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.9 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: 13122 Related Tickets: | Differential Rev(s): #8809,#10073,#10179,#12906,#13670 | Wiki Page: | -------------------------------------+------------------------------------- Changes (by gracjan): * cc: gracjan (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 9 16:08:22 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 09 Jun 2017 16:08:22 -0000 Subject: [GHC] #13804: MonoLocalBinds/RankNTypes type inference regression in GHC 8.2 In-Reply-To: <050.b9855b85679e008576846333f1b379f9@haskell.org> References: <050.b9855b85679e008576846333f1b379f9@haskell.org> Message-ID: <065.60a21d535937effbda36778a1b0ed141@haskell.org> #13804: MonoLocalBinds/RankNTypes type inference regression in GHC 8.2 -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: highest | Milestone: Component: Compiler (Type | Version: 8.2.1-rc2 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: #11698 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): I see what is happening here. We have {{{ f periph = let sr :: forall a. [a] -> [a] sr = ... periph ... sr' = sr in ... }}} Can we do type inference for `sr'`? Of course! Its only free var is `sr` which has a closed type. But from the point of view of static pointers, `sr'` mentions `sr` and `sr` mentions `periph`, so they could not be floated out. So they aren't closed in that sense. We were mixing the two up. Fix incoming. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 9 19:59:11 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 09 Jun 2017 19:59:11 -0000 Subject: =?utf-8?b?UmU6IFtHSENdICMxMzYxNTogTm9uZGV0ZXJtaW5pc20gaW4g4oCY?= =?utf-8?q?pure=E2=80=99_function_w/_parallel_evaluation_=26_memo?= =?utf-8?q?_combinators?= In-Reply-To: <044.57733831351687fff6258688df1f42f7@haskell.org> References: <044.57733831351687fff6258688df1f42f7@haskell.org> Message-ID: <059.7116ce9536a1c5d579ff559729bea960@haskell.org> #13615: Nondeterminism in ‘pure’ function w/ parallel evaluation & memo combinators -------------------------------------+------------------------------------- Reporter: pacak | Owner: bgamari Type: bug | Status: new Priority: highest | Milestone: 8.2.1 Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by dfeuer): I've written a [https://github.com/treeowl/unordered-containers/tree /super-safe seriously legitimate modification] of `Data.HashMap.Strict.fromListWith` that Ben indicates still demonstrates the problem. This version uses a separate type of mutable hashmap that holds `MArray`s. When it's done, it traverses the tree and (unsafely) freezes all the arrays. Unless I've goofed up, there should be no doubt that this version should work correctly. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 9 20:43:32 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 09 Jun 2017 20:43:32 -0000 Subject: =?utf-8?b?UmU6IFtHSENdICMxMzYxNTogTm9uZGV0ZXJtaW5pc20gaW4g4oCY?= =?utf-8?q?pure=E2=80=99_function_w/_parallel_evaluation_=26_memo?= =?utf-8?q?_combinators?= In-Reply-To: <044.57733831351687fff6258688df1f42f7@haskell.org> References: <044.57733831351687fff6258688df1f42f7@haskell.org> Message-ID: <059.cf800355bb2783447cdf5aeffbd9686b@haskell.org> #13615: Nondeterminism in ‘pure’ function w/ parallel evaluation & memo combinators -------------------------------------+------------------------------------- Reporter: pacak | Owner: bgamari Type: bug | Status: new Priority: highest | Milestone: 8.2.1 Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by dfeuer): * cc: dfeuer (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 9 20:57:41 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 09 Jun 2017 20:57:41 -0000 Subject: [GHC] #12390: List rules for `Coercible` instances In-Reply-To: <051.b98e23ec385e9c48fab8abae2b183162@haskell.org> References: <051.b98e23ec385e9c48fab8abae2b183162@haskell.org> Message-ID: <066.19949570d98a32a790ff77f470fcc1e8@haskell.org> #12390: List rules for `Coercible` instances -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: tellah Type: bug | Status: patch Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: ghci059 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3634 Wiki Page: | -------------------------------------+------------------------------------- Comment (by duog): The haddocks for Data.Coerce say it is a class, and include the ~R# constraint. Should this string also appear in the haddocks? Attaching the haddocks for Data.Coerce from HEAD. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 9 20:58:10 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 09 Jun 2017 20:58:10 -0000 Subject: [GHC] #12390: List rules for `Coercible` instances In-Reply-To: <051.b98e23ec385e9c48fab8abae2b183162@haskell.org> References: <051.b98e23ec385e9c48fab8abae2b183162@haskell.org> Message-ID: <066.624a5bbc70b86c37bf1423640acc6507@haskell.org> #12390: List rules for `Coercible` instances -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: tellah Type: bug | Status: patch Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: ghci059 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3634 Wiki Page: | -------------------------------------+------------------------------------- Changes (by duog): * Attachment "Data-Coerce.html" added. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 9 22:54:22 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 09 Jun 2017 22:54:22 -0000 Subject: [GHC] #13809: TH-reified data family instances have a paucity of kinds Message-ID: <050.0c3063c06a387a87a3b53a78ba487043@haskell.org> #13809: TH-reified data family instances have a paucity of kinds -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Template | Version: 8.0.1 Haskell | Keywords: TypeFamilies | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- Consider this data family (and instances): {{{#!hs {-# LANGUAGE TypeFamilies #-} module Foo where data family Foo a data instance Foo ((f :: * -> *) (a :: *)) data instance Foo ((f :: (* -> *) -> *) (a :: (* -> *))) }}} These are two data family instances that GHC distinguishes by the kinds of their type parameters. However, Template Haskell does not give me the same insight that GHC has, because if I call `Language.Haskell.TH.reify ''Foo`, I get this: {{{#!hs FamilyI (DataFamilyD Foo.Foo [ KindedTV a_6989586621679025989 StarT ] (Just StarT)) [ DataInstD [] Foo.Foo [ AppT (VarT f_6989586621679026001) (VarT a_6989586621679026000) ] Nothing [] [] , DataInstD [] Foo.Foo [ AppT (VarT f_6989586621679026007) (VarT a_6989586621679026006) ] Nothing [] [] ] }}} Note that neither `f` nor `a` have a kind signature in either instance! This makes it completely impossible to tell which is which (aside from the order, which is brittle). It would make my life a lot easier if TH were to include kind signatures for each type variable in a data family instance. I can see two ways to accomplish this: 1. Include a `[TyVarBndr]` field in `DataInstD` and `NewtypeInstD` where each `TyVarBndr` is a `KindedTV`. 2. Walk over the `Type`s in a `DataInstD`/`NewtypeInstD` and ensure that every occurrence of a `VarT` is surrounded with `SigT` to indicate its kind. While (1) is arguably the cleaner solution, since it makes the kinds easy to discover, it is a breaking change. Therefore, I'm inclined to implement option (2) instead. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 9 23:03:49 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 09 Jun 2017 23:03:49 -0000 Subject: [GHC] #13809: TH-reified type familly and data family instances have a paucity of kinds (was: TH-reified data family instances have a paucity of kinds) In-Reply-To: <050.0c3063c06a387a87a3b53a78ba487043@haskell.org> References: <050.0c3063c06a387a87a3b53a78ba487043@haskell.org> Message-ID: <065.ec8cc9839a282647c2f2638af0c1adb6@haskell.org> #13809: TH-reified type familly and data family instances have a paucity of kinds -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 8.0.1 Resolution: | Keywords: TypeFamilies Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): This also affects type family instances: {{{#!hs {-# LANGUAGE TypeFamilies #-} module Foo where type family Foo a type instance Foo ((f :: * -> *) (a :: *)) = Int type instance Foo ((f :: (* -> *) -> *) (a :: (* -> *))) = Char }}} {{{#!hs FamilyI (OpenTypeFamilyD (TypeFamilyHead Foo.Foo [ KindedTV a_6989586621679013859 StarT ] (KindSig StarT) Nothing)) [ TySynInstD Foo.Foo (TySynEqn [ AppT (VarT f_6989586621679013869) (VarT a_6989586621679013868) ] (ConT GHC.Types.Char)) , TySynInstD Foo.Foo (TySynEqn [ AppT (VarT f_6989586621679013874) (VarT a_6989586621679013873) ] (ConT GHC.Types.Int)) ] }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 9 23:15:22 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 09 Jun 2017 23:15:22 -0000 Subject: [GHC] #13809: TH-reified type familly and data family instances have a paucity of kinds In-Reply-To: <050.0c3063c06a387a87a3b53a78ba487043@haskell.org> References: <050.0c3063c06a387a87a3b53a78ba487043@haskell.org> Message-ID: <065.619927f98456bfdd62ec9b0ef91524ca@haskell.org> #13809: TH-reified type familly and data family instances have a paucity of kinds -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 8.0.1 Resolution: | Keywords: TypeFamilies Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #8953 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * related: => #8953 Comment: Ugh, and it affects class instances too: {{{#!hs {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE TypeFamilies #-} module Foo where class Foo a instance {-# OVERLAPPING #-} Foo ((f :: * -> *) (a :: *)) instance {-# OVERLAPPING #-} Foo ((f :: (* -> *) -> *) (a :: (* -> *))) }}} {{{#!hs ClassI (ClassD [] Foo.Foo [ KindedTV a_6989586621679013875 StarT ] [] []) [ InstanceD (Just Overlapping) [] (AppT (ConT Foo.Foo) (AppT (VarT f_6989586621679013885) (VarT a_6989586621679013886))) [] , InstanceD (Just Overlapping) [] (AppT (ConT Foo.Foo) (AppT (VarT f_6989586621679013890) (VarT a_6989586621679013891))) [] ] }}} Richard went part of the way in fixing these sorts of issues in #8953, but he avoided going too far in annotating every variable with a kind. Personally, I think he didn't go too far enough :) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jun 10 03:09:38 2017 From: ghc-devs at haskell.org (GHC) Date: Sat, 10 Jun 2017 03:09:38 -0000 Subject: [GHC] #13801: Make -main-is work with {thing} from arbitrary installed packages In-Reply-To: <050.8f0a9982543076f1b76bf433056aad58@haskell.org> References: <050.8f0a9982543076f1b76bf433056aad58@haskell.org> Message-ID: <065.091561258fb881a3a10ecfa604d360b1@haskell.org> #13801: Make -main-is work with {thing} from arbitrary installed packages -------------------------------------+------------------------------------- Reporter: SimonHengel | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by ezyang): So, are you aware that you can already refer to an identifier that is not defined in the Main module? The trick is that you have to export any of the identifiers you want to use. Here is a self-contained example: {{{ -- A.hs module A where f = print "This is A" -- Main.hs module Main(main, f) where import A main :: IO () main = return () }}} And then: `ghc --make Main.hs -main-is f`. Now, there are still things you might want to do... **You might want to not have to explicitly export f.** Then you would have to modify `checkMainExported`, and figure out if there was a technical reason why we required this (quite possibly because if it isn't exported, we will dead code eliminate it.) Maybe you should implicitly export any identifier mentioned with `-main-is`. That sounds helpful. **You might not want to have to import A.** In this case, you have to modify this code: {{{ getMainFun :: DynFlags -> RdrName getMainFun dflags = case mainFunIs dflags of Just fn -> mkRdrUnqual (mkVarOccFS (mkFastString fn)) Nothing -> main_RDR_Unqual }}} You'll have to take the module name, run it through the module lookup mechanism to make a Module, and then make an Orig RdrName. **You don't want to have to write main at all.** I think this is what you actually were asking for, based on the ticket text. In that case, GHC has to know that, if you pass `-main-is` and an empty list of modules, it should generate an empty source file (for Main), and then attempt to build that. You'd have to implement the previous step before that too. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jun 10 10:14:38 2017 From: ghc-devs at haskell.org (GHC) Date: Sat, 10 Jun 2017 10:14:38 -0000 Subject: [GHC] #13772: Cannot put HasCallStack on instances In-Reply-To: <047.d360e3ed5517211c4a279da62bac67fe@haskell.org> References: <047.d360e3ed5517211c4a279da62bac67fe@haskell.org> Message-ID: <062.c293602c4b3053fdccf035dd3bc07feb@haskell.org> #13772: Cannot put HasCallStack on instances -------------------------------------+------------------------------------- Reporter: augustss | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by augustss): So can you explain where I should put my HasCallstack constraint in my Monoid instance? I'd like to get a call stack when mempty is used and it calls error. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jun 10 10:21:41 2017 From: ghc-devs at haskell.org (GHC) Date: Sat, 10 Jun 2017 10:21:41 -0000 Subject: [GHC] #13773: Types are not normalized in instance declarations In-Reply-To: <047.b99d4e95d0428b43aa3236e584c6e7ac@haskell.org> References: <047.b99d4e95d0428b43aa3236e584c6e7ac@haskell.org> Message-ID: <062.a7583b9f8d926f39f5f593659e00516e@haskell.org> #13773: Types are not normalized in instance declarations -------------------------------------+------------------------------------- Reporter: augustss | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by augustss): No, I don't think GHC should accept (5*2) in a function definition. But I think it should accept my instance declaration. Here are two reasons: * GHC already does some normalization of types in instance declarations as it allows me to use type synonyms. * In the case of function definitions there is a workaround (guards), but there is no such workaround for instances. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jun 10 13:00:02 2017 From: ghc-devs at haskell.org (GHC) Date: Sat, 10 Jun 2017 13:00:02 -0000 Subject: [GHC] #6017: Reading ./.ghci files raises security issues In-Reply-To: <046.4c80215545a1055cdc72cec5a74c2a85@haskell.org> References: <046.4c80215545a1055cdc72cec5a74c2a85@haskell.org> Message-ID: <061.9460ea39f96dc8c2aa85c1e098bb0119@haskell.org> #6017: Reading ./.ghci files raises security issues -------------------------------------+------------------------------------- Reporter: nomeata | Owner: (none) Type: task | Status: new Priority: normal | Milestone: Component: GHCi | Version: 7.4.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Other | Test Case: Blocked By: | Blocking: Related Tickets: #8248 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by taylorfausak): I understand that this is an old issue, GHCi has behaved like this forever, and the `-ghci-script` workaround exists. Nonetheless this behavior always surprises and annoys me. Even if I run `chmod g-w .ghci` GHCi still complains that `. is writable by someone else` and ignores my `.ghci` file. I would like it if this permission check didn't exist at all, especially for directories and doubly so for `~/.ghci`. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jun 10 13:21:07 2017 From: ghc-devs at haskell.org (GHC) Date: Sat, 10 Jun 2017 13:21:07 -0000 Subject: [GHC] #13782: Bullish use of Template Haskell's newName causes GHC internal error In-Reply-To: <050.355b0f2ffb6750de858fbc3a1ccc85be@haskell.org> References: <050.355b0f2ffb6750de858fbc3a1ccc85be@haskell.org> Message-ID: <065.c59f0d0cb0784e0c6c3bfb641c82d74c@haskell.org> #13782: Bullish use of Template Haskell's newName causes GHC internal error -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: carlostome Type: bug | Status: new Priority: high | Milestone: 8.2.1 Component: Template Haskell | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: #12503 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by carlostome): * owner: (none) => carlostome Comment: Looking into it at ZuriHac, we suspect the function dropWildCards is where the problem lies. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jun 10 13:36:48 2017 From: ghc-devs at haskell.org (GHC) Date: Sat, 10 Jun 2017 13:36:48 -0000 Subject: [GHC] #13707: xmobar crashes with segmentation faults? In-Reply-To: <046.fbf7af7bdea4e00dc6b71cd4d89ec01e@haskell.org> References: <046.fbf7af7bdea4e00dc6b71cd4d89ec01e@haskell.org> Message-ID: <061.024f66bf0138e2ee1b2b11439d8020d6@haskell.org> #13707: xmobar crashes with segmentation faults? -------------------------------------+------------------------------------- Reporter: bgamari | Owner: (none) Type: bug | Status: infoneeded Priority: highest | Milestone: 8.2.1 Component: Compiler | Version: 8.2.1-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by trippels): Core dumps are disabled on my machine. And I have deleted the old crashing xmobar binary. Sorry, but I will not debug this any further and will just stay on 8.0.2 for the future. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jun 10 14:49:45 2017 From: ghc-devs at haskell.org (GHC) Date: Sat, 10 Jun 2017 14:49:45 -0000 Subject: [GHC] #13810: Gold linker fails Message-ID: <045.174b108f34b20d346eba46d31b44114b@haskell.org> #13810: Gold linker fails ----------------------------------------+--------------------------------- Reporter: ksaric | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Keywords: linker | Operating System: Linux Architecture: Unknown/Multiple | Type of failure: None/Unknown Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: ----------------------------------------+--------------------------------- When using gold linker in the project, the compilation fails. The same error occurs even when using nix, without stack. The bug can be reproduced very easily. You can clone from here (https://github.com/ksaric/bronze-linker) and `stack build`. Or you can: - `stack new project` - `cd project` - `stack build` Now it builds. - then add gold flags to cabal like here - https://github.com/ksaric /bronze-linker/blob/master/bronze-linker.cabal#L22-L25 - `stack build` Now it fails. ---- Linking .stack-work/dist/x86_64-linux-nix/Cabal-1.24.2.0/build/bronze- linker-exe/bronze-linker-exe ... /nix/store/x9v0yxy5iybp2m2ccqwqkvxgjy7zrw8f-binutils-2.28/bin/ld.gold: --hash-size=31: unknown option /nix/store/x9v0yxy5iybp2m2ccqwqkvxgjy7zrw8f-binutils-2.28/bin/ld.gold: use the --help option for usage information collect2: error: ld returned 1 exit status 'cc' failed in phase 'Linker'. (Exit code: 1) ---- -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jun 10 16:17:55 2017 From: ghc-devs at haskell.org (GHC) Date: Sat, 10 Jun 2017 16:17:55 -0000 Subject: [GHC] #13811: eta reduction in GHCi for an educational purpose Message-ID: <044.27eeea2d24b12962feca52e1f1460809@haskell.org> #13811: eta reduction in GHCi for an educational purpose -------------------------------------+------------------------------------- Reporter: vanto | Owner: (none) Type: feature | Status: new request | Priority: normal | Milestone: Component: GHCi | Version: 8.0.2 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- Hello,\\ Is it possible to have in GHCi an eta reduction of an expression for an educational purpose?\\ We would have access by typing a command like this on the line {{{:eta reduction }}} with the following annotation {{{show the eta reduction of }}} in short {{{:er }}}.\\ example:\\ {{{ Prelude> length xs = foldl (\n _ -> n+1) 0 xs Prelude> :eta reduction length --or :er length length = foldl (\n _ -> n+1) 0 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jun 10 20:55:02 2017 From: ghc-devs at haskell.org (GHC) Date: Sat, 10 Jun 2017 20:55:02 -0000 Subject: [GHC] #13009: Hierarchical Module Structure for GHC In-Reply-To: <045.859215149771e4346ac45f933feca22e@haskell.org> References: <045.859215149771e4346ac45f933feca22e@haskell.org> Message-ID: <060.14d848c0f80cff3ae7a0d5e916079968@haskell.org> #13009: Hierarchical Module Structure for GHC -------------------------------------+------------------------------------- Reporter: hsyl20 | Owner: hsyl20 Type: task | Status: new Priority: low | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | ModuleDependencies/Hierarchical | -------------------------------------+------------------------------------- Changes (by hsyl20): * owner: (none) => hsyl20 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jun 10 21:01:01 2017 From: ghc-devs at haskell.org (GHC) Date: Sat, 10 Jun 2017 21:01:01 -0000 Subject: [GHC] #13812: deriveConstants: no objdump program given (OpenBSD) Message-ID: <045.636d394562a9f1cf977240b7a6005dbd@haskell.org> #13812: deriveConstants: no objdump program given (OpenBSD) -------------------------------------+------------------------------------- Reporter: roland | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Build System | Version: Keywords: | Operating System: OpenBSD Architecture: | Type of failure: Building GHC Unknown/Multiple | failed Test Case: | Blocked By: Blocking: | Related Tickets: #9549 Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- Building HEAD on OpenBSD 6.1 fails with: {{{ inplace/bin/deriveConstants --gen-header -o includes/dist- derivedconstants/header/DerivedConstants.h --tmpdir includes/dist- derivedconstants/header/ --gcc-program "gcc" --gcc-flag -W all --gcc-flag -std=gnu99 --gcc-flag -fno-stack-protector --gcc-flag -Iincludes --gcc-flag -Iincludes/dist --gcc-flag -Iincludes/dist- derivedconstants/header --gcc-flag -Iincludes/di st-ghcconstants/header --gcc-flag -Irts --gcc-flag -fcommon --nm-program "nm" --target-os "openbsd" deriveConstants: no objdump program given }}} This can be fixed in configure.ac (see attached patch). -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jun 10 21:01:23 2017 From: ghc-devs at haskell.org (GHC) Date: Sat, 10 Jun 2017 21:01:23 -0000 Subject: [GHC] #13812: deriveConstants: no objdump program given (OpenBSD) In-Reply-To: <045.636d394562a9f1cf977240b7a6005dbd@haskell.org> References: <045.636d394562a9f1cf977240b7a6005dbd@haskell.org> Message-ID: <060.5727739d3fd7c557e91e6fdb74729234@haskell.org> #13812: deriveConstants: no objdump program given (OpenBSD) -------------------------------------+------------------------------------- Reporter: roland | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Build System | Version: Resolution: | Keywords: Operating System: OpenBSD | Architecture: Type of failure: Building GHC | Unknown/Multiple failed | Test Case: Blocked By: | Blocking: Related Tickets: #9549 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by roland): * Attachment "objdump.diff" added. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jun 10 21:20:12 2017 From: ghc-devs at haskell.org (GHC) Date: Sat, 10 Jun 2017 21:20:12 -0000 Subject: [GHC] #13810: Gold linker fails In-Reply-To: <045.174b108f34b20d346eba46d31b44114b@haskell.org> References: <045.174b108f34b20d346eba46d31b44114b@haskell.org> Message-ID: <060.f99f8bbf9eb04f6351ec53a91b0dbf1d@haskell.org> #13810: Gold linker fails ---------------------------------+---------------------------------------- Reporter: ksaric | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: linker Operating System: Linux | Architecture: Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | ---------------------------------+---------------------------------------- Comment (by domenkozar): Following fixes it: ``` diff --git a/bronze-linker.cabal b/bronze-linker.cabal index 548dbb9..00e0b5b 100644 --- a/bronze-linker.cabal +++ b/bronze-linker.cabal @@ -31,6 +31,8 @@ executable bronze-linker-exe build-depends: base , bronze-linker default-language: Haskell2010 + ghc-options: -optl-fuse-ld=gold + ld-options: -fuse-ld=gold test-suite bronze-linker-test type: exitcode-stdio-1.0 Discard this hunk from worktree [y,n,q,a,d,/,e,?]? y ``` -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jun 10 22:21:30 2017 From: ghc-devs at haskell.org (GHC) Date: Sat, 10 Jun 2017 22:21:30 -0000 Subject: [GHC] #13813: DeriveFunctor spuriously rejects existential context with type synonym mentioning the last type variable Message-ID: <050.a0d22a04ea0fb2e8ffd652ae181c7c5c@haskell.org> #13813: DeriveFunctor spuriously rejects existential context with type synonym mentioning the last type variable -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 (Type checker) | Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: GHC rejects Unknown/Multiple | valid program Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- This code does not compile: {{{#!hs {-# LANGUAGE ConstraintKinds #-} {-# LANGUAGE DeriveFunctor #-} {-# LANGUAGE ExistentialQuantification #-} {-# LANGUAGE KindSignatures #-} {-# LANGUAGE StandaloneDeriving #-} module Bug where import GHC.Exts (Constraint) type C (a :: Constraint) b = a data T a b = C (Show a) b => MkT b deriving instance Functor (T a) }}} {{{ GHCi, version 8.2.0.20170523: http://www.haskell.org/ghc/ :? for help Loaded GHCi configuration from /home/rgscott/.ghci [1 of 1] Compiling Bug ( Bug.hs, interpreted ) Bug.hs:13:1: error: • Can't make a derived instance of ‘Functor (T a)’: Constructor ‘MkT’ must be truly polymorphic in the last argument of the data type • In the stand-alone deriving instance for ‘Functor (T a)’ | 13 | deriving instance Functor (T a) | ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ }}} But it should, since if you expand `C (Show a) b`, you're left with `Show a`, which doesn't mention the last type variable `b` at all. Fix incoming. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jun 10 22:33:29 2017 From: ghc-devs at haskell.org (GHC) Date: Sat, 10 Jun 2017 22:33:29 -0000 Subject: [GHC] #13813: DeriveFunctor spuriously rejects existential context with type synonym mentioning the last type variable In-Reply-To: <050.a0d22a04ea0fb2e8ffd652ae181c7c5c@haskell.org> References: <050.a0d22a04ea0fb2e8ffd652ae181c7c5c@haskell.org> Message-ID: <065.11557a9f40e8d4c3cbdd98fe79cfedb7@haskell.org> #13813: DeriveFunctor spuriously rejects existential context with type synonym mentioning the last type variable -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: patch Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.1 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3635 Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * status: new => patch * differential: => Phab:D3635 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Jun 11 00:14:21 2017 From: ghc-devs at haskell.org (GHC) Date: Sun, 11 Jun 2017 00:14:21 -0000 Subject: [GHC] #13175: Documenting what can be derived 'out of the box' by GHC's "deriving" In-Reply-To: <046.ec8db13b6efff688fc4aec1eff3b3d67@haskell.org> References: <046.ec8db13b6efff688fc4aec1eff3b3d67@haskell.org> Message-ID: <061.ea9bf4f71375c264312d4577cdc7b785@haskell.org> #13175: Documenting what can be derived 'out of the box' by GHC's "deriving" -------------------------------------+------------------------------------- Reporter: carette | Owner: (none) Type: task | Status: new Priority: normal | Milestone: Component: Documentation | Version: 8.0.1 Resolution: | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: Type of failure: Documentation | Unknown/Multiple bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * keywords: => newcomer -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Jun 11 03:28:17 2017 From: ghc-devs at haskell.org (GHC) Date: Sun, 11 Jun 2017 03:28:17 -0000 Subject: [GHC] #13773: Types are not normalized in instance declarations In-Reply-To: <047.b99d4e95d0428b43aa3236e584c6e7ac@haskell.org> References: <047.b99d4e95d0428b43aa3236e584c6e7ac@haskell.org> Message-ID: <062.814c7428c23044766ad9a4551ec366ec@haskell.org> #13773: Types are not normalized in instance declarations -------------------------------------+------------------------------------- Reporter: augustss | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by ezyang): Related: #13262 which I think is asking for the same thing, but in a different context (it showed up in Backpack.) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Jun 11 07:30:38 2017 From: ghc-devs at haskell.org (GHC) Date: Sun, 11 Jun 2017 07:30:38 -0000 Subject: [GHC] #13814: Unable to resolve instance for polykinded superclass constraint on associated-type-family. Message-ID: <048.9b1676217a0776f27637f0af7f65030e@haskell.org> #13814: Unable to resolve instance for polykinded superclass constraint on associated-type-family. -------------------------------------+------------------------------------- Reporter: isovector | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Keywords: polykinds, | Operating System: Unknown/Multiple type families | Architecture: | Type of failure: GHC rejects Unknown/Multiple | valid program Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- The following program doesn't compile: {{{#!hs {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE PolyKinds #-} {-# LANGUAGE TypeFamilies #-} module Test where class Back k class Back (FrontBack k) => Front k where type FrontBack k :: k' instance Back Bool instance Front Int where type FrontBack Int = Bool }}} with the error message: {{{ • No instance for (Back (FrontBack Int)) arising from the superclasses of an instance declaration • In the instance declaration for ‘Front Int’ }}} The example successfully compiles if the kind annotation on FrontBack is removed. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Jun 11 07:36:09 2017 From: ghc-devs at haskell.org (GHC) Date: Sun, 11 Jun 2017 07:36:09 -0000 Subject: [GHC] #13814: Unable to resolve instance for polykinded superclass constraint on associated-type-family. In-Reply-To: <048.9b1676217a0776f27637f0af7f65030e@haskell.org> References: <048.9b1676217a0776f27637f0af7f65030e@haskell.org> Message-ID: <063.36f4f1308f535401209f554c68bea21c@haskell.org> #13814: Unable to resolve instance for polykinded superclass constraint on associated-type-family. -------------------------------------+------------------------------------- Reporter: isovector | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: polykinds, | type families Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Description changed by isovector: @@ -10,1 +10,1 @@ - class Back k + class Back t @@ -12,2 +12,2 @@ - class Back (FrontBack k) => Front k where - type FrontBack k :: k' + class Back (FrontBack t) => Front t where + type FrontBack t :: k New description: The following program doesn't compile: {{{#!hs {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE PolyKinds #-} {-# LANGUAGE TypeFamilies #-} module Test where class Back t class Back (FrontBack t) => Front t where type FrontBack t :: k instance Back Bool instance Front Int where type FrontBack Int = Bool }}} with the error message: {{{ • No instance for (Back (FrontBack Int)) arising from the superclasses of an instance declaration • In the instance declaration for ‘Front Int’ }}} The example successfully compiles if the kind annotation on FrontBack is removed. -- -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Jun 11 08:05:05 2017 From: ghc-devs at haskell.org (GHC) Date: Sun, 11 Jun 2017 08:05:05 -0000 Subject: [GHC] #13438: ghci :browse does not work with DuplicateRecordFields In-Reply-To: <042.11a55998df45140f6a656eacb5763ba3@haskell.org> References: <042.11a55998df45140f6a656eacb5763ba3@haskell.org> Message-ID: <057.329c8ac48cb9fc40bd3a8e268bdbfb52@haskell.org> #13438: ghci :browse does not work with DuplicateRecordFields -------------------------------------+------------------------------------- Reporter: rik | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: GHCi | Version: 8.0.2 Resolution: | Keywords: | duplicaterecordfields ghci orf Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Other | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by adamgundry): * keywords: duplicaterecordfields ghci => duplicaterecordfields ghci orf * cc: adamgundry (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Jun 11 08:06:23 2017 From: ghc-devs at haskell.org (GHC) Date: Sun, 11 Jun 2017 08:06:23 -0000 Subject: [GHC] #13352: Strange requirement for re-exported duplicate record fields In-Reply-To: <047.ff8942cd67c302be28d2cd71e3d50d5d@haskell.org> References: <047.ff8942cd67c302be28d2cd71e3d50d5d@haskell.org> Message-ID: <062.85706873c8cea9eb165d4a26b0ad8e28@haskell.org> #13352: Strange requirement for re-exported duplicate record fields -------------------------------------+------------------------------------- Reporter: crockeea | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.2 Resolution: | Keywords: orf Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by adamgundry): * keywords: => orf * cc: adamagundry (removed) * cc: adamgundry (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Jun 11 10:19:12 2017 From: ghc-devs at haskell.org (GHC) Date: Sun, 11 Jun 2017 10:19:12 -0000 Subject: [GHC] #13352: Strange requirement for re-exported duplicate record fields In-Reply-To: <047.ff8942cd67c302be28d2cd71e3d50d5d@haskell.org> References: <047.ff8942cd67c302be28d2cd71e3d50d5d@haskell.org> Message-ID: <062.69c7c807328f68baa60205014348ffe4@haskell.org> #13352: Strange requirement for re-exported duplicate record fields -------------------------------------+------------------------------------- Reporter: crockeea | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.2 Resolution: | Keywords: orf Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by adamgundry): Sorry, I've only just seen this as ezyang's CC missed. :( This is an awkward corner of the `DuplicateRecordFields` implementation: as you've observed, the extension needs to be enabled at the definition site of (all but one of) a set of record fields in order for them to be re-exported by a single module. In principle it would be possible to fix this by changing the implementation to mangle selector names regardless of whether the extension is enabled. However, I suspect this would be a nontrivial amount of work relative to the benefit. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Jun 11 10:50:10 2017 From: ghc-devs at haskell.org (GHC) Date: Sun, 11 Jun 2017 10:50:10 -0000 Subject: [GHC] #13792: Allow building using distro GCC on Windows In-Reply-To: <044.190a71c9e96d6252e4edbb8309f5384f@haskell.org> References: <044.190a71c9e96d6252e4edbb8309f5384f@haskell.org> Message-ID: <059.9cf97c4600837f5182e7519af9c8f118@haskell.org> #13792: Allow building using distro GCC on Windows -------------------------------------+------------------------------------- Reporter: Phyx- | Owner: Phyx- Type: feature request | Status: patch Priority: normal | Milestone: 8.4.1 Component: Build System | Version: 8.0.1 Resolution: | Keywords: Operating System: Windows | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3637 Wiki Page: | -------------------------------------+------------------------------------- Changes (by Phyx-): * status: new => patch * differential: => Phab:D3637 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Jun 11 10:59:55 2017 From: ghc-devs at haskell.org (GHC) Date: Sun, 11 Jun 2017 10:59:55 -0000 Subject: [GHC] #13815: Support Windows big-obj format Message-ID: <044.c8775a5b1225332f13eba63fedba7fc8@haskell.org> #13815: Support Windows big-obj format -------------------------------------+------------------------------------- Reporter: Phyx- | Owner: (none) Type: feature | Status: new request | Priority: normal | Milestone: 8.4.1 Component: Compiler | Version: 8.0.1 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): Phab:D3523 | Wiki Page: -------------------------------------+------------------------------------- By default, an object file can hold up to 65,536 (2^16) addressable sections. This is the case no matter which target platform is specified. /bigobj increases that address capacity to 4,294,967,296 (2^32). Most modules will never generate an .obj file that contains more than 65,536 sections. However, machine generated code, or code that makes heavy use of template libraries may require .obj files that can hold more sections. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Jun 11 11:00:46 2017 From: ghc-devs at haskell.org (GHC) Date: Sun, 11 Jun 2017 11:00:46 -0000 Subject: [GHC] #13815: Support Windows big-obj format In-Reply-To: <044.c8775a5b1225332f13eba63fedba7fc8@haskell.org> References: <044.c8775a5b1225332f13eba63fedba7fc8@haskell.org> Message-ID: <059.ccff36a99be6af9a297f2fc165ce1f1a@haskell.org> #13815: Support Windows big-obj format -------------------------------------+------------------------------------- Reporter: Phyx- | Owner: Phyx- Type: feature request | Status: new Priority: normal | Milestone: 8.4.1 Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3523 Wiki Page: | -------------------------------------+------------------------------------- Changes (by Phyx-): * owner: (none) => Phyx- @@ -1,1 +1,1 @@ - By default, an object file can hold up to 65,536 (2^16) addressable + By default, an object file can hold up to 65,536 `(2^16)` addressable @@ -3,1 +3,1 @@ - /bigobj increases that address capacity to 4,294,967,296 (2^32). + /bigobj increases that address capacity to 4,294,967,296 `(2^32)`. New description: By default, an object file can hold up to 65,536 `(2^16)` addressable sections. This is the case no matter which target platform is specified. /bigobj increases that address capacity to 4,294,967,296 `(2^32)`. Most modules will never generate an .obj file that contains more than 65,536 sections. However, machine generated code, or code that makes heavy use of template libraries may require .obj files that can hold more sections. -- -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Jun 11 11:00:57 2017 From: ghc-devs at haskell.org (GHC) Date: Sun, 11 Jun 2017 11:00:57 -0000 Subject: [GHC] #13815: Support Windows big-obj format In-Reply-To: <044.c8775a5b1225332f13eba63fedba7fc8@haskell.org> References: <044.c8775a5b1225332f13eba63fedba7fc8@haskell.org> Message-ID: <059.61b99004fefd086117ce0c3470910b8d@haskell.org> #13815: Support Windows big-obj format -------------------------------------+------------------------------------- Reporter: Phyx- | Owner: Phyx- Type: feature request | Status: patch Priority: normal | Milestone: 8.4.1 Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3523 Wiki Page: | -------------------------------------+------------------------------------- Changes (by Phyx-): * status: new => patch -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Jun 11 11:29:10 2017 From: ghc-devs at haskell.org (GHC) Date: Sun, 11 Jun 2017 11:29:10 -0000 Subject: [GHC] #13810: Gold linker fails In-Reply-To: <045.174b108f34b20d346eba46d31b44114b@haskell.org> References: <045.174b108f34b20d346eba46d31b44114b@haskell.org> Message-ID: <060.b57405d3b1a37f6225b3321786e92980@haskell.org> #13810: Gold linker fails ---------------------------------+---------------------------------------- Reporter: ksaric | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: linker Operating System: Linux | Architecture: Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | ---------------------------------+---------------------------------------- Comment (by ksaric): @domenkozar Ok, now I added the project https://github.com/ksaric/bronze-linker-client to try out. It depends on the project https://github.com/ksaric/bronze- linker and it doesn't compile. Also, I added three branches to the original project in question: - `demo/failing-example` - `demo/working-counter-example` - `demo/full-working` You can see that when using gold linker in the executable only, things work correctly - `demo/working-counter-example`. I'm not sure this is intentional, and I thought it's connected to the actual bug I found, which is that when you try to compile a project that has a dependency that uses gold linker, the aforementioned error occurs - you can reproduce that with the project I added - https://github.com/ksaric/bronze-linker-client. I hope this is clearer, and yes, I'm confused as well, this is kind of strange. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Jun 11 12:38:46 2017 From: ghc-devs at haskell.org (GHC) Date: Sun, 11 Jun 2017 12:38:46 -0000 Subject: [GHC] #8272: testing if SpLim=$rbp and Sp=$rsp changed performance at all In-Reply-To: <045.ecd7af4f53d7df1147bf6a068ec1e485@haskell.org> References: <045.ecd7af4f53d7df1147bf6a068ec1e485@haskell.org> Message-ID: <060.352dd7419e5c85c1cee7fbca4f7dcf8c@haskell.org> #8272: testing if SpLim=$rbp and Sp=$rsp changed performance at all -------------------------------------+------------------------------------- Reporter: carter | Owner: carter Type: task | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.7 Resolution: | Keywords: | callingConvention Operating System: Unknown/Multiple | Architecture: x86_64 Type of failure: Runtime | (amd64) performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonmar): > @simonmar the stack pointer experiment sans call and rest might still be worth measuring,yes? Having actual data would be a good starting point, but I'm not hopeful that it will be a win. > @simonmar: When you say "terrible time walking the stack", you mean GC, right? Yes, and exceptions and various other RTS routines that need to understand the stack. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Jun 11 14:44:03 2017 From: ghc-devs at haskell.org (GHC) Date: Sun, 11 Jun 2017 14:44:03 -0000 Subject: [GHC] #13808: Bump Cabal submodule In-Reply-To: <046.c4d8d53c6ca66b8eb549fabfe34bf347@haskell.org> References: <046.c4d8d53c6ca66b8eb549fabfe34bf347@haskell.org> Message-ID: <061.da5c56eb4c522b8506b9485a9a13942a@haskell.org> #13808: Bump Cabal submodule -------------------------------------+------------------------------------- Reporter: bgamari | Owner: (none) Type: bug | Status: new Priority: highest | Milestone: 8.2.1 Component: Compiler | Version: 8.2.1-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by refold): [https://github.com/haskell/cabal/releases/tag/Cabal-v2.0.0.1 Cabal-v2.0.0.1 tag] has been created. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Jun 11 15:29:32 2017 From: ghc-devs at haskell.org (GHC) Date: Sun, 11 Jun 2017 15:29:32 -0000 Subject: [GHC] #13814: Unable to resolve instance for polykinded superclass constraint on associated-type-family. In-Reply-To: <048.9b1676217a0776f27637f0af7f65030e@haskell.org> References: <048.9b1676217a0776f27637f0af7f65030e@haskell.org> Message-ID: <063.7c044a11c95455ce3a4a957cc2a2d6fa@haskell.org> #13814: Unable to resolve instance for polykinded superclass constraint on associated-type-family. -------------------------------------+------------------------------------- Reporter: isovector | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: polykinds, | type families Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): Very strange indeed. If you comment out the `Front Int` instance and inspect the file using GHCi and `-fprint-explicit-kinds`, you'll uncover something odd: {{{ GHCi, version 8.0.2: http://www.haskell.org/ghc/ :? for help Loaded GHCi configuration from /home/rgscott/.ghci [1 of 1] Compiling Test ( Bug.hs, interpreted ) Ok, modules loaded: Test. λ> :i Back class Back k (t :: k) -- Defined at Bug.hs:7:1 instance [safe] Back * Bool -- Defined at Bug.hs:12:10 λ> :i Front class Back (GHC.Prim.Any *) (FrontBack (GHC.Prim.Any *) k t) => Front k (t :: k) where type family FrontBack k1 k (t :: k) :: k1 -- Defined at Bug.hs:9:1 }}} The definition the `Back` class looks fine. But the definition of `Front` is quite bizarre! I'm not sure how `Any` is being introduced here, since I would have expected it to be this: {{{#!hs class Back k1 (FrontBack k1 k t) => Front k (t :: k) where type family FrontBack k1 k (t :: k) :: k1 }}} I suppose this also explains the confusing error message. If you try compiling the `Front Int` error message with `-fprint-explicit-kinds`, you'll see that: {{{ • No instance for (Back (GHC.Prim.Any *) (FrontBack (GHC.Prim.Any *) * Int)) arising from the superclasses of an instance declaration • In the instance declaration for ‘Front * Int’ }}} No wonder it's failing - we have an instance for `Back * (FrontBack * * Int)`, not for `Back (Any *) (FrontBack (Any *) * Int)`. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Jun 11 15:37:58 2017 From: ghc-devs at haskell.org (GHC) Date: Sun, 11 Jun 2017 15:37:58 -0000 Subject: [GHC] #13803: Panic while forcing the thunk for TyThing IsFile (regression) In-Reply-To: <044.5fd6949417f66553983c80f17489c157@haskell.org> References: <044.5fd6949417f66553983c80f17489c157@haskell.org> Message-ID: <059.817e887cfc8efc953cfbd3e06c0be9ed@haskell.org> #13803: Panic while forcing the thunk for TyThing IsFile (regression) -------------------------------------+------------------------------------- Reporter: inaki | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.1-rc2 Resolution: | Keywords: hs-boot Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by ezyang): It turns out this is not enough, if we actually need to test for overlap. Investigating. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Jun 11 15:38:17 2017 From: ghc-devs at haskell.org (GHC) Date: Sun, 11 Jun 2017 15:38:17 -0000 Subject: [GHC] #13739: Very slow linking of profiled executables In-Reply-To: <043.2d2650cd128632597774b5afb6c7a225@haskell.org> References: <043.2d2650cd128632597774b5afb6c7a225@haskell.org> Message-ID: <058.fcf90d1013c09107dd03bedf501ac887@haskell.org> #13739: Very slow linking of profiled executables -------------------------------------+------------------------------------- Reporter: duog | Owner: (none) Type: bug | Status: new Priority: high | Milestone: 8.2.1 Component: Compiler | Version: 8.2.1-rc2 Resolution: | Keywords: Operating System: Linux | Architecture: x86_64 Type of failure: Compile-time | (amd64) performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * priority: normal => high * milestone: => 8.2.1 Comment: Bumping the priority, as it would be nice to get some kind of resolution to this before GHC 8.2.1 is released. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Jun 11 17:48:24 2017 From: ghc-devs at haskell.org (GHC) Date: Sun, 11 Jun 2017 17:48:24 -0000 Subject: [GHC] #13803: Panic while forcing the thunk for TyThing IsFile (regression) In-Reply-To: <044.5fd6949417f66553983c80f17489c157@haskell.org> References: <044.5fd6949417f66553983c80f17489c157@haskell.org> Message-ID: <059.79aff5d768395b19775dfc530187b5e2@haskell.org> #13803: Panic while forcing the thunk for TyThing IsFile (regression) -------------------------------------+------------------------------------- Reporter: inaki | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.1-rc2 Resolution: | Keywords: hs-boot Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by ezyang): So, here is a test case which is not solved by the test above: {{{ -- F.hs {-# LANGUAGE TypeFamilies #-} module F where type family F a :: * -- A.hs-boot module A where data T -- B.hs {-# LANGUAGE TypeFamilies #-} module B where import {-# SOURCE #-} A import F type instance F T = Int -- C.hs {-# LANGUAGE TypeFamilies #-} module C where import {-# SOURCE #-} A import F type instance F T = Bool -- A.hs module A where import B import C }}} Right now, we decide to defer a type family consistency check if the family was recursively defined. If the RHS refers to a recursively defined type, there's no problem: we don't need to look at it for consistency checking. But if the LHS is recursively defined, as is in this example, we DO need to defer the check. But it's a bit irritating to figure out whether or not there's actually a reference to a recursively defined type in the LHS, since this involves traversing the LHS types, and if we're not careful we'll end up pulling in the TyThing anyway. There are two other possibilities: (1) always defer checking instances which are defined inside the recursive look (by looking at the Name of the axiom), or (2) annotating IfaceAxiom with the set of boot types its LHS refers to, for easy checking. Not entirely sure what the best action is. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Jun 11 17:53:56 2017 From: ghc-devs at haskell.org (GHC) Date: Sun, 11 Jun 2017 17:53:56 -0000 Subject: [GHC] #13810: Gold linker fails In-Reply-To: <045.174b108f34b20d346eba46d31b44114b@haskell.org> References: <045.174b108f34b20d346eba46d31b44114b@haskell.org> Message-ID: <060.1b84cecab25ed46ec726c7bc253b9e9f@haskell.org> #13810: Gold linker fails ---------------------------------+---------------------------------------- Reporter: ksaric | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: linker Operating System: Linux | Architecture: Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | ---------------------------------+---------------------------------------- Comment (by domenkozar): So here's my understanding how bug happens on GHC 8.0.2: If library A is linked with gold and library B depends on A, no matter if B is specified to be linked with gold or not, it fails to detect that it should use the gold linker. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Jun 11 20:58:07 2017 From: ghc-devs at haskell.org (GHC) Date: Sun, 11 Jun 2017 20:58:07 -0000 Subject: [GHC] #13810: Gold linker fails In-Reply-To: <045.174b108f34b20d346eba46d31b44114b@haskell.org> References: <045.174b108f34b20d346eba46d31b44114b@haskell.org> Message-ID: <060.76f6c9f72e48c3fdc9a43a0bfe63ca85@haskell.org> #13810: Gold linker fails ---------------------------------+---------------------------------------- Reporter: ksaric | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: linker Operating System: Linux | Architecture: Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | ---------------------------------+---------------------------------------- Comment (by ksaric): Right. And if you try to explicitly add gold linker flags to library B, it doesn't help, since GHC thinks (heh, I wish) that it doesn't need to use gold linker for project A, even if the project A has defined gold linker explicitly. Anyone can try to modify the project https://github.com/ksaric/bronze- linker-client with the flags and without them, and **it will fail in both cases**. So: - project A is using gold linker - project B is using project A ''Project B can't compile because it's sending parameters for "regular" ld, and not gold linker.'' -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Jun 11 23:18:33 2017 From: ghc-devs at haskell.org (GHC) Date: Sun, 11 Jun 2017 23:18:33 -0000 Subject: [GHC] #13773: Types are not normalized in instance declarations In-Reply-To: <047.b99d4e95d0428b43aa3236e584c6e7ac@haskell.org> References: <047.b99d4e95d0428b43aa3236e584c6e7ac@haskell.org> Message-ID: <062.7c61ff1d5339b1d9aab77dc3eb3eb46a@haskell.org> #13773: Types are not normalized in instance declarations -------------------------------------+------------------------------------- Reporter: augustss | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by goldfire): Care to write a [https://github.com/ghc-proposals/ghc-proposals ghc- proposal]? I don't much like this new idea, and comment:10:ticket:13262 suggests that Simon PJ doesn't either, but perhaps others do. I think the best way to find out is to make a proposal. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Jun 11 23:24:13 2017 From: ghc-devs at haskell.org (GHC) Date: Sun, 11 Jun 2017 23:24:13 -0000 Subject: [GHC] #13811: eta reduction in GHCi for an educational purpose In-Reply-To: <044.27eeea2d24b12962feca52e1f1460809@haskell.org> References: <044.27eeea2d24b12962feca52e1f1460809@haskell.org> Message-ID: <059.6175fe7f3ea0bf31c995ebb404d426bc@haskell.org> #13811: eta reduction in GHCi for an educational purpose -------------------------------------+------------------------------------- Reporter: vanto | Owner: (none) Type: feature request | Status: closed Priority: normal | Milestone: Component: GHCi | Version: 8.0.2 Resolution: invalid | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by goldfire): * status: new => closed * resolution: => invalid Comment: My instinct is that this feature is beyond the scope of GHCi and is better incorporated into another tool (perhaps [https://github.com/HeinrichApfelmus/hyper-haskell HyperHaskell]?), but others may differ in opinion. Regardless of my opinion on the feature, the way to incorporate this user-facing change is to write a [https://github.com/ghc-proposals/ghc-proposals ghc-proposal]. I'll also note that this will be hard to implement, as GHC does not store the user-written definition of functions anywhere. Given that this belongs as a ghc-proposal instead of a Trac ticket, I will close. This ticket can be reopened when the proposal is accepted. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Jun 11 23:39:28 2017 From: ghc-devs at haskell.org (GHC) Date: Sun, 11 Jun 2017 23:39:28 -0000 Subject: [GHC] #13809: TH-reified type familly and data family instances have a paucity of kinds In-Reply-To: <050.0c3063c06a387a87a3b53a78ba487043@haskell.org> References: <050.0c3063c06a387a87a3b53a78ba487043@haskell.org> Message-ID: <065.e840f63ea04ef0816ac3f0ae413f2525@haskell.org> #13809: TH-reified type familly and data family instances have a paucity of kinds -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 8.0.1 Resolution: | Keywords: TypeFamilies Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #8953 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by goldfire): I prefer design (1). Design (1) also jibes with a ghc-proposal I'm about to submit, allowing the user to write an explicit `forall` attached to any class/type/data instance (including equations of a closed type family). Others may feel differently, though. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Jun 11 23:53:40 2017 From: ghc-devs at haskell.org (GHC) Date: Sun, 11 Jun 2017 23:53:40 -0000 Subject: [GHC] #12390: List rules for `Coercible` instances In-Reply-To: <051.b98e23ec385e9c48fab8abae2b183162@haskell.org> References: <051.b98e23ec385e9c48fab8abae2b183162@haskell.org> Message-ID: <066.e17519c043e9424cbd8cb86bc57f83fa@haskell.org> #12390: List rules for `Coercible` instances -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: tellah Type: bug | Status: patch Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: ghci059 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3634 Wiki Page: | -------------------------------------+------------------------------------- Comment (by goldfire): Here are some design notes off the top of my head: I don't want to clutter `TyThing` with this, as it's unclear where within `TyThing` the documentation should go. In `TyCon`? Perhaps, but I don't love it. Instead, `InteractiveEval.getInfo` could return 5 things instead of 4; the fifth is an `SDoc` with extra text that should be printed. (It would normally be `empty`.) Naturally, you will have to add the fifth return value to `HscMain.hscTcRnGetInfo` and `TcRnDriver.tcRnGetInfo`. That last function can just call a new `lookupCustomDoc` function. That function can be defined in `PrelInfo`; it would refer to a `UniqFM SDoc` that associates `Unique`s with `SDoc`s. The `SDoc`s could (for now) just be hard-coded in `PrelInfo`. Certainly baked-in goodies other than `Coercible` can benefit from this new behavior. Perhaps it would be better to store the printed strings outside of a Haskell source file, but we don't have to over-design to begin with. Before implementing this, @tellah, perhaps someone else who is not a newcomer can opine on my design choices here. And, thanks! -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 12 00:11:18 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 12 Jun 2017 00:11:18 -0000 Subject: [GHC] #9173: Better type error messages In-Reply-To: <046.f8f24aa2ddaa3d579bc40f0b6f04f6b7@haskell.org> References: <046.f8f24aa2ddaa3d579bc40f0b6f04f6b7@haskell.org> Message-ID: <061.f2b6f4012f302155cb47bd95b2942b83@haskell.org> #9173: Better type error messages -------------------------------------+------------------------------------- Reporter: simonpj | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.8.2 Resolution: | Keywords: | TypeErrorMessages Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by sgillespie): I would love to look into this, but it is unclear what the new message is supposed to be. Should we go with the suggestion of the original post, or one of the other rewording suggestions? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 12 01:36:18 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 12 Jun 2017 01:36:18 -0000 Subject: [GHC] #9173: Better type error messages In-Reply-To: <046.f8f24aa2ddaa3d579bc40f0b6f04f6b7@haskell.org> References: <046.f8f24aa2ddaa3d579bc40f0b6f04f6b7@haskell.org> Message-ID: <061.4953912fb3b65f056a13cda7b6a77d4b@haskell.org> #9173: Better type error messages -------------------------------------+------------------------------------- Reporter: simonpj | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.8.2 Resolution: | Keywords: | TypeErrorMessages Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): I like the extension of rwbarton's proposal from comment:11, {{{ Couldn't match actual type ‘[Char]’ with type ‘Int’ expected by context In the expression: "Howdy!" }}} Seems like a simple yet clear change. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 12 01:50:51 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 12 Jun 2017 01:50:51 -0000 Subject: [GHC] #13812: deriveConstants: no objdump program given (OpenBSD) In-Reply-To: <045.636d394562a9f1cf977240b7a6005dbd@haskell.org> References: <045.636d394562a9f1cf977240b7a6005dbd@haskell.org> Message-ID: <060.eb5a5c533bdb91013a20733c70e887dc@haskell.org> #13812: deriveConstants: no objdump program given (OpenBSD) -------------------------------------+------------------------------------- Reporter: roland | Owner: (none) Type: bug | Status: patch Priority: normal | Milestone: Component: Build System | Version: Resolution: | Keywords: Operating System: OpenBSD | Architecture: Type of failure: Building GHC | Unknown/Multiple failed | Test Case: Blocked By: | Blocking: Related Tickets: #9549 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => patch Comment: Thanks for the patch! It looks like AIX also requires `objdump`. I'll amend the patch accordingly when I merge it. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 12 02:11:14 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 12 Jun 2017 02:11:14 -0000 Subject: [GHC] #12582: HSOC Eventlog live profiling In-Reply-To: <047.39614347d19ac7526209a37004883cae@haskell.org> References: <047.39614347d19ac7526209a37004883cae@haskell.org> Message-ID: <062.078d9b4df58a8955f22396f1c04de38e@haskell.org> #12582: HSOC Eventlog live profiling -------------------------------------+------------------------------------- Reporter: NCrashed | Owner: NCrashed Type: feature request | Status: closed Priority: normal | Milestone: 8.2.1 Component: Runtime System | Version: 8.0.1 Resolution: fixed | Keywords: eventlog | profile hsoc Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2522 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => closed * resolution: => fixed * milestone: => 8.2.1 Comment: For the record, we have merged a simple variant of the original patch in Phab:D2934. I think this can be closed. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 12 02:11:29 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 12 Jun 2017 02:11:29 -0000 Subject: [GHC] #12582: HSOC Eventlog live profiling In-Reply-To: <047.39614347d19ac7526209a37004883cae@haskell.org> References: <047.39614347d19ac7526209a37004883cae@haskell.org> Message-ID: <062.6370063bf2bc03112299cb397d79d4a5@haskell.org> #12582: HSOC Eventlog live profiling -------------------------------------+------------------------------------- Reporter: NCrashed | Owner: NCrashed Type: feature request | Status: closed Priority: normal | Milestone: 8.2.1 Component: Runtime System | Version: 8.0.1 Resolution: fixed | Keywords: eventlog | profile hsoc Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2522, Wiki Page: | Phab:D2934 -------------------------------------+------------------------------------- Changes (by bgamari): * differential: Phab:D2522 => Phab:D2522, Phab:D2934 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 12 03:11:20 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 12 Jun 2017 03:11:20 -0000 Subject: [GHC] #13809: TH-reified type familly and data family instances have a paucity of kinds In-Reply-To: <050.0c3063c06a387a87a3b53a78ba487043@haskell.org> References: <050.0c3063c06a387a87a3b53a78ba487043@haskell.org> Message-ID: <065.2ef1ec0ab3bbf35c86171ed7d15c3dec@haskell.org> #13809: TH-reified type familly and data family instances have a paucity of kinds -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 8.0.1 Resolution: | Keywords: TypeFamilies Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #8953 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by goldfire): That ghc-proposal is discussed [https://github.com/ghc-proposals/ghc- proposals/pull/55 here]. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 12 09:09:05 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 12 Jun 2017 09:09:05 -0000 Subject: [GHC] #12970: Add default implementation for Bits.bitSize In-Reply-To: <045.18bc248265b05555e123c1ad78e88bb9@haskell.org> References: <045.18bc248265b05555e123c1ad78e88bb9@haskell.org> Message-ID: <060.2ad7e7fb236a24828dfc633ad02b05c2@haskell.org> #12970: Add default implementation for Bits.bitSize -------------------------------------+------------------------------------- Reporter: txnull | Owner: (none) Type: feature request | Status: upstream Priority: normal | Milestone: Component: libraries/base | Version: Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by txnull): Any news on the issue? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 12 09:52:05 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 12 Jun 2017 09:52:05 -0000 Subject: [GHC] #13816: make phase1 fails with clang error on Mac OS X El Capitan Message-ID: <044.dad7278a0f298c880e344d26abcde905@haskell.org> #13816: make phase1 fails with clang error on Mac OS X El Capitan -------------------------------------+------------------------------------- Reporter: bollu | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- `make` fails with the following build output at phase1: {{{ ╭─bollu at cantordust ~/work/ghc-all/ghc/libraries ‹2.3.1› ‹master*› ╰─$ export CC=gcc; export CXX=g++; CC=gcc CXX=g++ make 130 ↵ /Applications/Xcode.app/Contents/Developer/usr/bin/make -C .. all_libraries ===--- building phase 0 /Applications/Xcode.app/Contents/Developer/usr/bin/make --no-print- directory -f ghc.mk phase=0 phase_0_builds make[2]: Nothing to be done for `phase_0_builds'. ===--- building phase 1 /Applications/Xcode.app/Contents/Developer/usr/bin/make --no-print- directory -f ghc.mk phase=1 phase_1_builds utils/unlit/ghc.mk:33: utils/unlit/dist/build/.depend.c_asm: No such file or directory utils/hp2ps/ghc.mk:43: utils/hp2ps/dist/build/.depend.c_asm: No such file or directory utils/genapply/ghc.mk:23: utils/genapply/dist/build/.depend.haskell: No such file or directory utils/genapply/ghc.mk:23: utils/genapply/dist/build/.depend.c_asm: No such file or directory libraries/hpc/ghc.mk:3: libraries/hpc/dist-boot/build/.depend-v.haskell: No such file or directory libraries/hpc/ghc.mk:3: libraries/hpc/dist-boot/build/.depend-v.c_asm: No such file or directory libraries/binary/ghc.mk:3: libraries/binary/dist- boot/build/.depend-v.haskell: No such file or directory libraries/binary/ghc.mk:3: libraries/binary/dist- boot/build/.depend-v.c_asm: No such file or directory libraries/Cabal/Cabal/ghc.mk:3: libraries/Cabal/Cabal/dist- boot/build/.depend-v.haskell: No such file or directory libraries/Cabal/Cabal/ghc.mk:3: libraries/Cabal/Cabal/dist- boot/build/.depend-v.c_asm: No such file or directory libraries/ghc-boot-th/ghc.mk:3: libraries/ghc-boot-th/dist- boot/build/.depend-v.haskell: No such file or directory libraries/ghc-boot-th/ghc.mk:3: libraries/ghc-boot-th/dist- boot/build/.depend-v.c_asm: No such file or directory libraries/ghc-boot/ghc.mk:3: libraries/ghc-boot/dist- boot/build/.depend-v.haskell: No such file or directory libraries/ghc-boot/ghc.mk:3: libraries/ghc-boot/dist- boot/build/.depend-v.c_asm: No such file or directory libraries/template-haskell/ghc.mk:3: libraries/template-haskell/dist- boot/build/.depend-v.haskell: No such file or directory libraries/template-haskell/ghc.mk:3: libraries/template-haskell/dist- boot/build/.depend-v.c_asm: No such file or directory libraries/hoopl/ghc.mk:3: libraries/hoopl/dist- boot/build/.depend-v.haskell: No such file or directory libraries/hoopl/ghc.mk:3: libraries/hoopl/dist-boot/build/.depend-v.c_asm: No such file or directory libraries/transformers/ghc.mk:3: libraries/transformers/dist- boot/build/.depend-v.haskell: No such file or directory libraries/transformers/ghc.mk:3: libraries/transformers/dist- boot/build/.depend-v.c_asm: No such file or directory libraries/text/ghc.mk:3: libraries/text/dist-boot/build/.depend-v.haskell: No such file or directory libraries/text/ghc.mk:3: libraries/text/dist-boot/build/.depend-v.c_asm: No such file or directory libraries/terminfo/ghc.mk:3: libraries/terminfo/dist- boot/build/.depend-v.haskell: No such file or directory libraries/terminfo/ghc.mk:3: libraries/terminfo/dist- boot/build/.depend-v.c_asm: No such file or directory libraries/ghci/ghc.mk:3: libraries/ghci/dist-boot/build/.depend-v.haskell: No such file or directory libraries/ghci/ghc.mk:3: libraries/ghci/dist-boot/build/.depend-v.c_asm: No such file or directory compiler/ghc.mk:590: compiler/stage1/build/.depend-v.haskell: No such file or directory utils/ghc-pkg/ghc.mk:70: utils/ghc-pkg/dist/build/.depend.haskell: No such file or directory "rm" -f utils/ghc-pkg/dist/build/.depend.haskell.tmp "/usr/local/bin/ghc" -M -static -H32m -O -Wall -package-db libraries/bootstrapping.conf -hide-all-packages -i -iutils/ghc-pkg/. -iutils/ghc-pkg/dist/build -Iutils/ghc-pkg/dist/build -iutils/ghc- pkg/dist/build/ghc-pkg/autogen -Iutils/ghc-pkg/dist/build/ghc-pkg/autogen -optP-DWITH_TERMINFO -optP-include -optPutils/ghc-pkg/dist/build/ghc- pkg/autogen/cabal_macros.h -package-id base-4.9.1.0 -package-id directory-1.3.0.0 -package-id process-1.4.3.0 -package-id containers-0.5.7.1 -package-id filepath-1.4.1.1 -package-id Cabal-2.0.0.0 -package-id binary-0.8.4.1 -package-id ghc-boot-8.3 -package-id bytestring-0.10.8.1 -package-id terminfo-0.4.1.0 -package-id unix-2.7.2.1 -XHaskell2010 -no-user-package-db -rtsopts -odir utils/ghc- pkg/dist/build -hidir utils/ghc-pkg/dist/build -stubdir utils/ghc- pkg/dist/build -dep-makefile utils/ghc-pkg/dist/build/.depend.haskell.tmp -dep-suffix "" -include-pkg-deps utils/ghc-pkg/./Main.hs utils/ghc- pkg/dist/build/Version.hs utils/ghc-pkg/Main.hs:1451:40: error: error: editor placeholder in source file then termText (location db) <#> termText "\n (no packages)\n" ^ 1 error generated. `clang' failed in phase `C pre-processor'. (Exit code: 1) make[2]: *** [utils/ghc-pkg/dist/build/.depend.haskell] Error 1 make[1]: *** [all_libraries] Error 2 make: *** [all] Error 2 }}} g++ version: {{{ ╭─bollu at cantordust ~/work/ghc-all/ghc/libraries ‹2.3.1› ‹master*› ╰─$ g++ --version 2 ↵ Configured with: --prefix=/Applications/Xcode.app/Contents/Developer/usr --with-gxx-include-dir=/usr/include/c++/4.2.1 Apple LLVM version 7.3.0 (clang-703.0.31) Target: x86_64-apple-darwin15.6.0 Thread model: posix InstalledDir: /Applications/Xcode.app/Contents/Developer/Toolchains/XcodeDefault.xctoolchain/usr/bin }}} GCC version: {{{ ╭─bollu at cantordust ~/work/ghc-all/ghc/libraries ‹2.3.1› ‹master*› ╰─$ gcc --version Configured with: --prefix=/Applications/Xcode.app/Contents/Developer/usr --with-gxx-include-dir=/usr/include/c++/4.2.1 Apple LLVM version 7.3.0 (clang-703.0.31) Target: x86_64-apple-darwin15.6.0 Thread model: posix InstalledDir: /Applications/Xcode.app/Contents/Developer/Toolchains/XcodeDefault.xctoolchain/usr/bin }}} GHC version: {{{ ╭─bollu at cantordust ~/work/ghc-all/ghc/libraries ‹2.3.1› ‹master*› ╰─$ ghc --version The Glorious Glasgow Haskell Compilation System, version 8.0.2 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 12 11:41:46 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 12 Jun 2017 11:41:46 -0000 Subject: [GHC] #13817: Simplifier and SpecConstr performance regression with 8.2.1 Message-ID: <047.0d86e1522b2fc42732f7ab726cf6825d@haskell.org> #13817: Simplifier and SpecConstr performance regression with 8.2.1 -------------------------------------+------------------------------------- Reporter: albertov | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.1-rc1 Keywords: | Operating System: Linux Architecture: | Type of failure: Compile-time Unknown/Multiple | performance bug Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- A propietary application I've upgraded to compile with 8.2.1-rc1 makes GHC manifest a performance regression when producing optimized ({{{-O2}}}) code. After a crude analysis of a compile log produced with {{{-show-passes}}} it appears that the biggest slowdown is in the Simplifier and SpecConstr phases when compiling the "main" modules. Theres a conversation at GHC Users with more details: https://mail.haskell.org/pipermail/glasgow-haskell- users/2017-June/026543.html. The data, the results and the script to to analyse it live at: https://gist.github.com/albertov/145ac5c01bfbadc5c9ff55e9c5c2e50e I'll try to update this ticket with a way to to reproduce it as soon as I can (if I can) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 12 13:44:02 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 12 Jun 2017 13:44:02 -0000 Subject: [GHC] #13817: Simplifier and SpecConstr performance regression with 8.2.1 In-Reply-To: <047.0d86e1522b2fc42732f7ab726cf6825d@haskell.org> References: <047.0d86e1522b2fc42732f7ab726cf6825d@haskell.org> Message-ID: <062.99b6e72de63142d1776e0bae7ddbb0d4@haskell.org> #13817: Simplifier and SpecConstr performance regression with 8.2.1 -------------------------------------+------------------------------------- Reporter: albertov | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.1-rc1 Resolution: | Keywords: Operating System: Linux | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): How big is the slow-down? On the thread you also mentioned that execution time has improved significantly. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 12 14:01:50 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 12 Jun 2017 14:01:50 -0000 Subject: [GHC] #13816: make phase1 fails with clang error on Mac OS X El Capitan In-Reply-To: <044.dad7278a0f298c880e344d26abcde905@haskell.org> References: <044.dad7278a0f298c880e344d26abcde905@haskell.org> Message-ID: <059.4aca7f592dbe0bdffc6891eb61b2e558@haskell.org> #13816: make phase1 fails with clang error on Mac OS X El Capitan -------------------------------------+------------------------------------- Reporter: bollu | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: duplicate | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #13805 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => closed * resolution: => duplicate * related: => #13805 Comment: This is a duplicate of #13805. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 12 14:03:12 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 12 Jun 2017 14:03:12 -0000 Subject: [GHC] #13805: GHC 8.0.2 fails to build on macOS 10.13/Xcode 9 - preprocessor error in ghc-pkg In-Reply-To: <049.5c553f223a194e22fdf785f7cd8ea0f5@haskell.org> References: <049.5c553f223a194e22fdf785f7cd8ea0f5@haskell.org> Message-ID: <064.1d8656eb683c3a32e976090059c9d45e@haskell.org> #13805: GHC 8.0.2 fails to build on macOS 10.13/Xcode 9 - preprocessor error in ghc-pkg -------------------------------------+------------------------------------- Reporter: mistydemeo | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: ghc-pkg | Version: 8.0.2 Resolution: | Keywords: Operating System: MacOS X | Architecture: x86_64 Type of failure: Building GHC | (amd64) failed | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): It looks like we need to pass ` -fno-allow-editor-placeholders` in `CFLAGS`. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 12 15:21:45 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 12 Jun 2017 15:21:45 -0000 Subject: [GHC] #13805: GHC 8.0.2 fails to build on macOS 10.13/Xcode 9 - preprocessor error in ghc-pkg In-Reply-To: <049.5c553f223a194e22fdf785f7cd8ea0f5@haskell.org> References: <049.5c553f223a194e22fdf785f7cd8ea0f5@haskell.org> Message-ID: <064.6594f9e967dbeed0b48cbd0655bf2b31@haskell.org> #13805: GHC 8.0.2 fails to build on macOS 10.13/Xcode 9 - preprocessor error in ghc-pkg -------------------------------------+------------------------------------- Reporter: mistydemeo | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: ghc-pkg | Version: 8.0.2 Resolution: | Keywords: Operating System: MacOS X | Architecture: x86_64 Type of failure: Building GHC | (amd64) failed | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by mistydemeo): After looking into it, I think the problem is that the editor placeholder check is too lax, which I've reported to clang with a patch: https://bugs.llvm.org/show_bug.cgi?id=33394 `<#>` doesn't meet the requirements because it has only a single hash, but the check matched it by accident. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 12 16:27:38 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 12 Jun 2017 16:27:38 -0000 Subject: [GHC] #13805: GHC 8.0.2 fails to build on macOS 10.13/Xcode 9 - preprocessor error in ghc-pkg In-Reply-To: <049.5c553f223a194e22fdf785f7cd8ea0f5@haskell.org> References: <049.5c553f223a194e22fdf785f7cd8ea0f5@haskell.org> Message-ID: <064.ddfd1b1cfbb27ca0c2f493f2a8e75105@haskell.org> #13805: GHC 8.0.2 fails to build on macOS 10.13/Xcode 9 - preprocessor error in ghc-pkg -------------------------------------+------------------------------------- Reporter: mistydemeo | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: ghc-pkg | Version: 8.0.2 Resolution: | Keywords: Operating System: MacOS X | Architecture: x86_64 Type of failure: Building GHC | (amd64) failed | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by bollu): This was "fixed" for me by installing `gcc` and changing the settings file at `/usr/local/lib/ghc-8.0.2/settings` to: {{{ ... ("Haskell CPP command","gcc"), ("Haskell CPP flags","-E -undef -traditional -Wno-invalid-pp-token -Wno- unicode -Wno-trigraphs"), ... }}} (I replaced `clang` with `gcc`) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 12 16:37:48 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 12 Jun 2017 16:37:48 -0000 Subject: [GHC] #13809: TH-reified type familly and data family instances have a paucity of kinds In-Reply-To: <050.0c3063c06a387a87a3b53a78ba487043@haskell.org> References: <050.0c3063c06a387a87a3b53a78ba487043@haskell.org> Message-ID: <065.56ff0ebef479323764b838c1118a12ee@haskell.org> #13809: TH-reified type familly and data family instances have a paucity of kinds -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 8.0.1 Resolution: | Keywords: TypeFamilies Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #8953 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): Ah. I suppose if we're going to be adding `foralls` to instances anyways, then option (1) is the only sensible one. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 12 16:56:32 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 12 Jun 2017 16:56:32 -0000 Subject: [GHC] #13407: Fix printing of higher-rank kinds In-Reply-To: <047.e0e70f9dcf452b0789ae502f43b96326@haskell.org> References: <047.e0e70f9dcf452b0789ae502f43b96326@haskell.org> Message-ID: <062.a78eb1c4beb56995e7a11be59451a039@haskell.org> #13407: Fix printing of higher-rank kinds -------------------------------------+------------------------------------- Reporter: goldfire | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: TypeInType Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): Another higher-rank kind pretty-printing oddity: {{{#!hs {-# LANGUAGE RankNTypes #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE TypeInType #-} module Bug where import Data.Kind type family Foo (a :: Type) :: Type type instance Foo (a :: forall k. k -> Type) = Int }}} {{{ GHCi, version 8.2.0.20170523: http://www.haskell.org/ghc/ :? for help Loaded GHCi configuration from /home/rgscott/.ghci [1 of 1] Compiling Bug ( Bug.hs, interpreted ) Bug.hs:9:19: error: • Expecting one more argument to ‘a k1’ Expected a type, but ‘a k1’ has kind ‘k1 -> *’ • In the first argument of ‘Foo’, namely ‘(a :: forall k. k -> Type)’ In the type instance declaration for ‘Foo’ | 9 | type instance Foo (a :: forall k. k -> Type) = Int | ^^^^^^^^^^^^^^^^^^^^^^^^^^ }}} The error message mentions `a k1`... how did that `k1` sneak in there? I'm not sure if it's due to the same root cause as the original issue, but thought it was worth mentioning. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 12 18:02:16 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 12 Jun 2017 18:02:16 -0000 Subject: [GHC] #12970: Add default implementation for Bits.bitSize In-Reply-To: <045.18bc248265b05555e123c1ad78e88bb9@haskell.org> References: <045.18bc248265b05555e123c1ad78e88bb9@haskell.org> Message-ID: <060.c6199f3ab08a051934d28f1132c83e2c@haskell.org> #12970: Add default implementation for Bits.bitSize -------------------------------------+------------------------------------- Reporter: txnull | Owner: (none) Type: feature request | Status: upstream Priority: normal | Milestone: Component: libraries/base | Version: Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by ekmett): We deprecated bitSize back in 7.8. Removing it outright in 8.4 seems to be a reasonably measured move and would preempt the need for this default. I'm rather inclined to say we should just finish removing it. Either way, we're now past the window in which we should do anyhing either way that would affect 8.2. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 12 18:15:59 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 12 Jun 2017 18:15:59 -0000 Subject: [GHC] #13818: ANN pragmas and -static fail to compile Message-ID: <043.c516255f7dad6e8df1c98c0695419dd5@haskell.org> #13818: ANN pragmas and -static fail to compile -------------------------------------+------------------------------------- Reporter: duog | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.1-rc2 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- A Haskell source file with an ANN pragma will fail to compile with -static if any packages do not have dynamic libraries installed. Reproduction: {{{ $ echo "module Bug where {-# ANN module "just a string" #-}" > Bug.hs $ cabal sandbox init $ cabal install transformers-compat --disable-shared $ ghc -static -package db ./.cabal-sandbox/x86_64-linux- ghc-8.2.0.20170522-packages.conf.d -package transformers-compat -c Bug.hs : can't load .so/.DLL for: libHStransformers- compat-0.5.1.4-DQiwI4tzfvoKHf8rERr8Q2.so (libHStransformers- compat-0.5.1.4-DQiwI4tzfvoKHf8rERr8Q2.so: cannot open shared object file: No such file or directory) $ cabal install transformers-compat --enable-shared --reinstall $ ghc -static -package db ./.cabal-sandbox/x86_64-linux- ghc-7.10.3-packages.conf.d -package transformers-compat -c Bug.hs -fforce-recomp }}} Presumably the ANN pragma causes ghci to load with all libraries which must be dynamic. Not sure which category is correct for Type of failure. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 12 18:18:28 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 12 Jun 2017 18:18:28 -0000 Subject: [GHC] #13818: ANN pragmas and -static fails to compile if dynamic library unavailable (was: ANN pragmas and -static fail to compile) In-Reply-To: <043.c516255f7dad6e8df1c98c0695419dd5@haskell.org> References: <043.c516255f7dad6e8df1c98c0695419dd5@haskell.org> Message-ID: <058.5fff6da14b03172f5feb50f6a8d3f01b@haskell.org> #13818: ANN pragmas and -static fails to compile if dynamic library unavailable -------------------------------------+------------------------------------- Reporter: duog | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.1-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 12 18:19:17 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 12 Jun 2017 18:19:17 -0000 Subject: [GHC] #13818: ANN pragmas and -static fails to compile if dynamic library unavailable In-Reply-To: <043.c516255f7dad6e8df1c98c0695419dd5@haskell.org> References: <043.c516255f7dad6e8df1c98c0695419dd5@haskell.org> Message-ID: <058.f34db4bc47ac3848e87ee3da153a1a13@haskell.org> #13818: ANN pragmas and -static fails to compile if dynamic library unavailable -------------------------------------+------------------------------------- Reporter: duog | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.1-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Description changed by duog: @@ -6,1 +6,1 @@ - $ echo "module Bug where {-# ANN module "just a string" #-}" > Bug.hs + $ echo "module Bug where {-# ANN module \"just a string\" #-}" > Bug.hs New description: A Haskell source file with an ANN pragma will fail to compile with -static if any packages do not have dynamic libraries installed. Reproduction: {{{ $ echo "module Bug where {-# ANN module \"just a string\" #-}" > Bug.hs $ cabal sandbox init $ cabal install transformers-compat --disable-shared $ ghc -static -package db ./.cabal-sandbox/x86_64-linux- ghc-8.2.0.20170522-packages.conf.d -package transformers-compat -c Bug.hs : can't load .so/.DLL for: libHStransformers- compat-0.5.1.4-DQiwI4tzfvoKHf8rERr8Q2.so (libHStransformers- compat-0.5.1.4-DQiwI4tzfvoKHf8rERr8Q2.so: cannot open shared object file: No such file or directory) $ cabal install transformers-compat --enable-shared --reinstall $ ghc -static -package db ./.cabal-sandbox/x86_64-linux- ghc-7.10.3-packages.conf.d -package transformers-compat -c Bug.hs -fforce-recomp }}} Presumably the ANN pragma causes ghci to load with all libraries which must be dynamic. Not sure which category is correct for Type of failure. -- -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 12 18:20:23 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 12 Jun 2017 18:20:23 -0000 Subject: [GHC] #13818: ANN pragmas and -static fails to compile if dynamic library unavailable In-Reply-To: <043.c516255f7dad6e8df1c98c0695419dd5@haskell.org> References: <043.c516255f7dad6e8df1c98c0695419dd5@haskell.org> Message-ID: <058.a82e405084bc45646260ad2c415d4f2a@haskell.org> #13818: ANN pragmas and -static fails to compile if dynamic library unavailable -------------------------------------+------------------------------------- Reporter: duog | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.1-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Description changed by duog: @@ -17,1 +17,1 @@ - ghc-7.10.3-packages.conf.d -package transformers-compat -c Bug.hs + ghc-8.2.0.20170522-packages.conf.d -package transformers-compat -c Bug.hs New description: A Haskell source file with an ANN pragma will fail to compile with -static if any packages do not have dynamic libraries installed. Reproduction: {{{ $ echo "module Bug where {-# ANN module \"just a string\" #-}" > Bug.hs $ cabal sandbox init $ cabal install transformers-compat --disable-shared $ ghc -static -package db ./.cabal-sandbox/x86_64-linux- ghc-8.2.0.20170522-packages.conf.d -package transformers-compat -c Bug.hs : can't load .so/.DLL for: libHStransformers- compat-0.5.1.4-DQiwI4tzfvoKHf8rERr8Q2.so (libHStransformers- compat-0.5.1.4-DQiwI4tzfvoKHf8rERr8Q2.so: cannot open shared object file: No such file or directory) $ cabal install transformers-compat --enable-shared --reinstall $ ghc -static -package db ./.cabal-sandbox/x86_64-linux- ghc-8.2.0.20170522-packages.conf.d -package transformers-compat -c Bug.hs -fforce-recomp }}} Presumably the ANN pragma causes ghci to load with all libraries which must be dynamic. Not sure which category is correct for Type of failure. -- -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 12 18:35:16 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 12 Jun 2017 18:35:16 -0000 Subject: [GHC] #11953: Export Word32#, Word64# on all architectures In-Reply-To: <046.593317f13858c2d1c5dc11a464cab3d1@haskell.org> References: <046.593317f13858c2d1c5dc11a464cab3d1@haskell.org> Message-ID: <061.5133537d47f2c43f1571f241e21f31ae@haskell.org> #11953: Export Word32#, Word64# on all architectures -------------------------------------+------------------------------------- Reporter: bgamari | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: 8.4.1 Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by michalt): * cc: michalt (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 12 18:47:37 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 12 Jun 2017 18:47:37 -0000 Subject: [GHC] #13691: Bump time submodule In-Reply-To: <046.7033f0ecc0a7c3600b088ca823c99a67@haskell.org> References: <046.7033f0ecc0a7c3600b088ca823c99a67@haskell.org> Message-ID: <061.56ae6e859e2cf424dcfdc72607af797c@haskell.org> #13691: Bump time submodule -------------------------------------+------------------------------------- Reporter: bgamari | Owner: (none) Type: task | Status: new Priority: highest | Milestone: 8.2.1 Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): The issue isn't a build failure. Rather, the behavior of the library is buggy. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 12 18:55:11 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 12 Jun 2017 18:55:11 -0000 Subject: [GHC] #9173: Better type error messages In-Reply-To: <046.f8f24aa2ddaa3d579bc40f0b6f04f6b7@haskell.org> References: <046.f8f24aa2ddaa3d579bc40f0b6f04f6b7@haskell.org> Message-ID: <061.beeb7f0a3908896d9288cddebb9ee7fa@haskell.org> #9173: Better type error messages -------------------------------------+------------------------------------- Reporter: simonpj | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.8.2 Resolution: | Keywords: | TypeErrorMessages Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by vanto): I agree with bgamari too.\\ Well, I glanced at the Oxford Dictionary. I have compared the words "context" and "signature".\\ Here is the definition of the word "context":\\ - The circumstances that form the setting for an event, statement, or idea, and in terms of which it can be fully understood.\\ Examples:\\ ‘the proposals need to be considered in the context of new European directives’\\ ‘We are going to be able, within a European context, to be in a more positive position.’\\ ‘This is down to his determination to place current events in a historical context.’\\ ‘For new readers this can be an advantage, but they become disadvantages in contexts of closer study.’\\\\ Synonyms of the word context: circumstances, conditions, surroundings, factors, state of affairs\\ frame of reference, contextual relationship.\\ \\ Here is the definition of the word "signature":\\ - A distinctive pattern, product, or characteristic by which someone or something can be identified.\\ Examples:\\ ‘the chef produced the pâté that was his signature’\\ ‘Changes in population size tend to leave recognizable signatures in the patterns of nucleotide diversity.’\\ ‘This process, called intrinsic catalysis, has a characteristic signature in the exchange time measurements versus pH.’\\ ‘Cells tugged in one direction sent biochemical signals in the opposite direction in the form of a signature pattern of fluorescent light.’\\\\ Obviously, the word signature has a more precise meaning, characterizing a thing and the word context has a broader meaning. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 12 20:05:35 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 12 Jun 2017 20:05:35 -0000 Subject: [GHC] #13782: Bullish use of Template Haskell's newName causes GHC internal error In-Reply-To: <050.355b0f2ffb6750de858fbc3a1ccc85be@haskell.org> References: <050.355b0f2ffb6750de858fbc3a1ccc85be@haskell.org> Message-ID: <065.feddb866df23608cfcbc7d58c56b935b@haskell.org> #13782: Bullish use of Template Haskell's newName causes GHC internal error -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: carlostome Type: bug | Status: new Priority: high | Milestone: 8.2.1 Component: Template Haskell | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: #12503 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by carlostome): After some debugging I found out that the bug arises in the following function from [https://git.haskell.org/ghc.git/blob/HEAD:/compiler/rename/RnTypes.hs#l1711 RnTypes] {{{ #!haskell extract_hs_tv_bndrs :: [LHsTyVarBndr GhcPs] -> FreeKiTyVars -> FreeKiTyVars -> RnM FreeKiTyVars -- In (forall (a :: Maybe e). a -> b) we have -- 'a' is bound by the forall -- 'b' is a free type variable -- 'e' is a free kind variable extract_hs_tv_bndrs tvs (FKTV acc_kvs acc_k_set acc_tvs acc_t_set acc_all) -- Note accumulator comes first (FKTV body_kvs body_k_set body_tvs body_t_set body_all) | null tvs = return $ FKTV (body_kvs ++ acc_kvs) (body_k_set `unionOccSets` acc_k_set) (body_tvs ++ acc_tvs) (body_t_set `unionOccSets` acc_t_set) (body_all ++ acc_all) | otherwise = do { FKTV bndr_kvs bndr_k_set _ _ _ <- foldrM extract_lkind emptyFKTV [k | L _ (KindedTyVar _ k) <- tvs] ; let locals = mkOccSet $ map (rdrNameOcc . hsLTyVarName) tvs ; return $ FKTV (filterOut ((`elemOccSet` locals) . rdrNameOcc . unLoc) (bndr_kvs ++ body_kvs) ++ acc_kvs) ((body_k_set `minusOccSet` locals) `unionOccSets` acc_k_set `unionOccSets` bndr_k_set) (filterOut ((`elemOccSet` locals) . rdrNameOcc . unLoc) body_tvs ++ acc_tvs) ((body_t_set `minusOccSet` locals) `unionOccSets` acc_t_set) (filterOut ((`elemOccSet` locals) . rdrNameOcc . unLoc) (bndr_kvs ++ body_all) ++ acc_all) } }}} In the case ''tvs'' is empty, the '''locals''' variable holds the set of OccName found in tvs. The OccName of variable ''a2'' in the program with the line: {{{#!haskell [f,a2] <- mapM newName ["f","a"] }}} is 'a' and thus the variable is filtered out from ''bndr_kvs ++ body_kvs'' (Which I guess holds the variable 'a' from ''data Maybe a''). However, in the program with the line: {{{#!haskell [f,a2] <- mapM newName ["f","b"] }}} the ''OccName'' of ''a2'' is "b" and doesn't get filtered out because it's OccName is not "a". In the previous version of the commit 6746549772c5cc0ac66c0fce562f297f4d4b80a2 that changed this function, the variables where filtered regarding the full name (Which in this case is a ''Exact'' name) not only its OccName and the problem didn't existed. I guess one way to solve this would be to filter out again based on full names and not only the ''OccName'' of variables. Any thoughts? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 12 20:38:59 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 12 Jun 2017 20:38:59 -0000 Subject: [GHC] #12970: Add default implementation for Bits.bitSize In-Reply-To: <045.18bc248265b05555e123c1ad78e88bb9@haskell.org> References: <045.18bc248265b05555e123c1ad78e88bb9@haskell.org> Message-ID: <060.88738ec391492287fb10129858ea4a62@haskell.org> #12970: Add default implementation for Bits.bitSize -------------------------------------+------------------------------------- Reporter: txnull | Owner: (none) Type: feature request | Status: upstream Priority: high | Milestone: 8.4.1 Component: libraries/base | Version: Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * priority: normal => high * milestone: => 8.4.1 Comment: Sounds good to me, let's remove it for 8.4. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 12 20:49:13 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 12 Jun 2017 20:49:13 -0000 Subject: [GHC] #13819: GHC Panics Message-ID: <051.cbfd374163652d5209657cd86d4948f0@haskell.org> #13819: GHC Panics -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- {{{#!hs {-# LANGUAGE DeriveFunctor, TypeApplications #-} -- {-# Language ViewPatterns #-} -- {-# Language InstanceSigs, ViewPatterns, TupleSections, GeneralizedNewtypeDeriving, TemplateHaskell, LambdaCase #-} module D where import Data.Coerce import Control.Applicative newtype A a = A (IO a) deriving Functor instance Applicative A where pure = pure @(_ -> WrappedMonad A _) @(_ -> A _) pure instance Monad A where }}} causes a panic {{{ $ ghci -ignore-dot-ghci /tmp/a.hs GHCi, version 8.3.20170605: http://www.haskell.org/ghc/ :? for help [1 of 1] Compiling D ( /tmp/a.hs, interpreted ) ghc: panic! (the 'impossible' happened) (GHC version 8.3.20170605 for x86_64-unknown-linux): repSplitAppTys w0_a1xc[tau:4] WrappedMonad A w0_a1xe[tau:4] [] Call stack: CallStack (from HasCallStack): prettyCurrentCallStack, called at compiler/utils/Outputable.hs:1133:58 in ghc:Outputable callStackDoc, called at compiler/utils/Outputable.hs:1137:37 in ghc:Outputable pprPanic, called at compiler/types/Type.hs:809:9 in ghc:Type Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug > }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 12 20:49:28 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 12 Jun 2017 20:49:28 -0000 Subject: [GHC] #13819: GHC Panics In-Reply-To: <051.cbfd374163652d5209657cd86d4948f0@haskell.org> References: <051.cbfd374163652d5209657cd86d4948f0@haskell.org> Message-ID: <066.717d63b38ce2d5aadbd4bb202e0c93bb@haskell.org> #13819: GHC Panics -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by Iceland_jack): * version: 8.0.1 => 8.3 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 12 20:59:42 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 12 Jun 2017 20:59:42 -0000 Subject: [GHC] #13793: Simple program trips checkNurserySanity() In-Reply-To: <046.a36b0da0c049dac7c618bbfdc92da5ef@haskell.org> References: <046.a36b0da0c049dac7c618bbfdc92da5ef@haskell.org> Message-ID: <061.1006d2742065df81ed6325af2f66d715@haskell.org> #13793: Simple program trips checkNurserySanity() -------------------------------------+------------------------------------- Reporter: niteria | Owner: niteria Type: bug | Status: new Priority: normal | Milestone: Component: Runtime System | Version: 8.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: x86_64 | (amd64) Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): Any motion towards a fix? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 12 21:05:35 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 12 Jun 2017 21:05:35 -0000 Subject: [GHC] #13793: Simple program trips checkNurserySanity() In-Reply-To: <046.a36b0da0c049dac7c618bbfdc92da5ef@haskell.org> References: <046.a36b0da0c049dac7c618bbfdc92da5ef@haskell.org> Message-ID: <061.c2595822ebc1b07d8e8f46e5aba6ead6@haskell.org> #13793: Simple program trips checkNurserySanity() -------------------------------------+------------------------------------- Reporter: niteria | Owner: niteria Type: bug | Status: new Priority: normal | Milestone: Component: Runtime System | Version: 8.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: x86_64 | (amd64) Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by niteria): I'm working on it in parallel with other things. Would it help to have it sooner rather than later? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 12 21:08:18 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 12 Jun 2017 21:08:18 -0000 Subject: [GHC] #13773: Types are not normalized in instance declarations In-Reply-To: <047.b99d4e95d0428b43aa3236e584c6e7ac@haskell.org> References: <047.b99d4e95d0428b43aa3236e584c6e7ac@haskell.org> Message-ID: <062.efe6c28e9a4cef58a60d1268d084af43@haskell.org> #13773: Types are not normalized in instance declarations -------------------------------------+------------------------------------- Reporter: augustss | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by augustss): The only way I know how to get around this would be to use CPP, and to me that is a serious code smell. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 12 21:33:51 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 12 Jun 2017 21:33:51 -0000 Subject: [GHC] #13819: TypeApplications-related GHC panic (was: GHC Panics) In-Reply-To: <051.cbfd374163652d5209657cd86d4948f0@haskell.org> References: <051.cbfd374163652d5209657cd86d4948f0@haskell.org> Message-ID: <066.6d717d6ed55b47db8846f48a75d2b639@haskell.org> #13819: TypeApplications-related GHC panic -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: bug | Status: new Priority: high | Milestone: 8.2.1 Component: Compiler (Type | Version: 8.2.1-rc2 checker) | Keywords: Resolution: | TypeApplications Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * component: Compiler => Compiler (Type checker) * priority: normal => high * failure: None/Unknown => Compile-time crash or panic * version: 8.3 => 8.2.1-rc2 * milestone: => 8.2.1 * keywords: => TypeApplications Comment: Yikes, this is a regression from GHC 8.0.2. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 12 21:34:54 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 12 Jun 2017 21:34:54 -0000 Subject: [GHC] #13820: GHC goes out of memory while compiling nothing Message-ID: <045.02f4d99bdc465f78bea41f2d527be881@haskell.org> #13820: GHC goes out of memory while compiling nothing -------------------------------------+------------------------------------- Reporter: seunje | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- Compiling this results in GHC using all memory and eventually segfaulting {{{#!haskell f = id id id id id id id id id id id id id id id id id id id id id id id id id id id main = print 1 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 12 21:42:36 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 12 Jun 2017 21:42:36 -0000 Subject: [GHC] #13820: GHC goes out of memory while compiling nothing In-Reply-To: <045.02f4d99bdc465f78bea41f2d527be881@haskell.org> References: <045.02f4d99bdc465f78bea41f2d527be881@haskell.org> Message-ID: <060.361d9bfc3a80794d9daa33c3141913ae@haskell.org> #13820: GHC goes out of memory while compiling nothing -------------------------------------+------------------------------------- Reporter: seunje | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): The fact that this uses a lot of memory is entirely unsurprising, as https://stackoverflow.com/questions/23746852/why-does-haskells-do-nothing- function-id-consume-tons-of-memory documents. I'm surprised that it segfaults, however. How much memory does your system have? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 12 21:54:06 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 12 Jun 2017 21:54:06 -0000 Subject: [GHC] #13407: Fix printing of higher-rank kinds In-Reply-To: <047.e0e70f9dcf452b0789ae502f43b96326@haskell.org> References: <047.e0e70f9dcf452b0789ae502f43b96326@haskell.org> Message-ID: <062.b921011ab4f4da473716de0999db9940@haskell.org> #13407: Fix printing of higher-rank kinds -------------------------------------+------------------------------------- Reporter: goldfire | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: TypeInType Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): Remember that teh arguments in a type instance are types, not type variables. So when you write {{{ type instance Foo (a :: forall k. k-> TYpe) = ... }}} GHC treats it much like {{{ -- Suppose T :: forall k. k -> Type type instance Foo T = ... }}} It'll instantaite `T`'s kind to give `T k1` (where `k1` is a unification variable. Then it'll to unify `k1->Type` with the expected argument kind of `F`, namely `Type`. Hence the error mesage. Th eoddity is that it prints `a k1` rather than just `a` even without `fprint-explicit-kinds`. I expect that's because the head isn't at type constructor, but rather a type variable -- a pretty-printing bug. But a palpable bug, I think. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 12 22:21:53 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 12 Jun 2017 22:21:53 -0000 Subject: [GHC] #13782: Bullish use of Template Haskell's newName causes GHC internal error In-Reply-To: <050.355b0f2ffb6750de858fbc3a1ccc85be@haskell.org> References: <050.355b0f2ffb6750de858fbc3a1ccc85be@haskell.org> Message-ID: <065.f22ccb9d72e6f7d50fab6545758a2930@haskell.org> #13782: Bullish use of Template Haskell's newName causes GHC internal error -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: carlostome Type: bug | Status: new Priority: high | Milestone: 8.2.1 Component: Template Haskell | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: #12503 | Differential Rev(s): Phab:D3641 Wiki Page: | -------------------------------------+------------------------------------- Changes (by carlostome): * differential: => Phab:D3641 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 12 22:30:12 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 12 Jun 2017 22:30:12 -0000 Subject: [GHC] #13819: TypeApplications-related GHC panic In-Reply-To: <051.cbfd374163652d5209657cd86d4948f0@haskell.org> References: <051.cbfd374163652d5209657cd86d4948f0@haskell.org> Message-ID: <066.955ebb259d65fca536eac4d0855eb60f@haskell.org> #13819: TypeApplications-related GHC panic -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: bug | Status: new Priority: high | Milestone: 8.2.1 Component: Compiler (Type | Version: 8.2.1-rc2 checker) | Keywords: Resolution: | TypeApplications Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * cc: goldfire (added) Comment: Richard, this is yet more fallout from the terrible `uo_thing` mess. The panic comes from the argument-counting in `repSplitAppTys`, when called from `mkTypErrorThing` or `mkTypeErrorThingArgs`. At the moment we construct this `ErrorThing` the kind of the type has not been zonked, so we have a `FunTy t1 t2` with `t1 :: kappa`. I guess this will be fixed when we tidy up `uo_thing`... but that is looking increasingly urgent. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 12 22:47:12 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 12 Jun 2017 22:47:12 -0000 Subject: [GHC] #13782: Bullish use of Template Haskell's newName causes GHC internal error In-Reply-To: <050.355b0f2ffb6750de858fbc3a1ccc85be@haskell.org> References: <050.355b0f2ffb6750de858fbc3a1ccc85be@haskell.org> Message-ID: <065.e0ccaf566a5fe6551d6da27f5361a177@haskell.org> #13782: Bullish use of Template Haskell's newName causes GHC internal error -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: carlostome Type: bug | Status: new Priority: high | Milestone: 8.2.1 Component: Template Haskell | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: #12503 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * cc: goldfire (added) * differential: Phab:D3641 => Comment: Yes, I think you are right. For some undocumented reason, Richard, you changed this function to manipulate {{{ data FreeKiTyVars = FKTV { fktv_kis :: [Located RdrName] , _fktv_k_set :: OccSet -- for efficiency, -- only used internally , fktv_tys :: [Located RdrName] , _fktv_t_set :: OccSet , fktv_all :: [Located RdrName] } }}} instead of just the `fktv_kis` and `fktv_tys` pair which it used before. Moreover you switched to using `OccNames` for equality rather than `RdrNames`. Might you fix? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 12 23:12:20 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 12 Jun 2017 23:12:20 -0000 Subject: [GHC] #8809: Prettier error messages? In-Reply-To: <047.4dbdad421fcd945584d210433034ccb5@haskell.org> References: <047.4dbdad421fcd945584d210433034ccb5@haskell.org> Message-ID: <062.87200c1367eb4507671cfee5a283db13@haskell.org> #8809: Prettier error messages? -------------------------------------+------------------------------------- Reporter: joelteon | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.9 Resolution: | Keywords: | TYpeErrorMessages Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: 13122 Related Tickets: | Differential Rev(s): #8809,#10073,#10179,#12906,#13670 | Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * keywords: => TYpeErrorMessages -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 12 23:12:41 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 12 Jun 2017 23:12:41 -0000 Subject: [GHC] #8809: Prettier error messages? In-Reply-To: <047.4dbdad421fcd945584d210433034ccb5@haskell.org> References: <047.4dbdad421fcd945584d210433034ccb5@haskell.org> Message-ID: <062.366c8a8259da41b6cc97c5e5fb7605c6@haskell.org> #8809: Prettier error messages? -------------------------------------+------------------------------------- Reporter: joelteon | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.9 Resolution: | Keywords: | TypeErrorMessages Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: 13122 Related Tickets: | Differential Rev(s): #8809,#10073,#10179,#12906,#13670 | Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * keywords: TYpeErrorMessages => TypeErrorMessages -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 12 23:27:13 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 12 Jun 2017 23:27:13 -0000 Subject: [GHC] #13739: Very slow linking of profiled executables In-Reply-To: <043.2d2650cd128632597774b5afb6c7a225@haskell.org> References: <043.2d2650cd128632597774b5afb6c7a225@haskell.org> Message-ID: <058.c1bc9d2dcda74c23c43a211c27492087@haskell.org> #13739: Very slow linking of profiled executables -------------------------------------+------------------------------------- Reporter: duog | Owner: (none) Type: bug | Status: new Priority: high | Milestone: 8.2.1 Component: Compiler | Version: 8.2.1-rc2 Resolution: | Keywords: Operating System: Linux | Architecture: x86_64 Type of failure: Compile-time | (amd64) performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by duog): * Attachment "T13739-check-ld" added. Script to time ghc with different versions of ld -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 12 23:28:32 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 12 Jun 2017 23:28:32 -0000 Subject: [GHC] #13739: Very slow linking of profiled executables In-Reply-To: <043.2d2650cd128632597774b5afb6c7a225@haskell.org> References: <043.2d2650cd128632597774b5afb6c7a225@haskell.org> Message-ID: <058.5a1945c3611cfd1d9c39f1ba0a608362@haskell.org> #13739: Very slow linking of profiled executables -------------------------------------+------------------------------------- Reporter: duog | Owner: (none) Type: bug | Status: new Priority: high | Milestone: 8.2.1 Component: Compiler | Version: 8.2.1-rc2 Resolution: | Keywords: Operating System: Linux | Architecture: x86_64 Type of failure: Compile-time | (amd64) performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by duog): * Attachment "T13739-check-ld-output" added. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 12 23:30:48 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 12 Jun 2017 23:30:48 -0000 Subject: [GHC] #13814: Unable to resolve instance for polykinded superclass constraint on associated-type-family. In-Reply-To: <048.9b1676217a0776f27637f0af7f65030e@haskell.org> References: <048.9b1676217a0776f27637f0af7f65030e@haskell.org> Message-ID: <063.eb41db213d4571b50e43f17ae1c8b6f4@haskell.org> #13814: Unable to resolve instance for polykinded superclass constraint on associated-type-family. -------------------------------------+------------------------------------- Reporter: isovector | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: polykinds, | type families Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): You say you expected {{{ class Back k1 (FrontBack k1 k t) => Front k (t :: k) where ... }}} But this is jolly odd, becuase the constraint mentions `k1`, which is not bound in the bit after the `=>`. Would you expect this to be OK? {{{ class C a b => D a where op1 :: a -> Int -> a }}} Well no! Think of the data type declaration that arises from class decl: {{{ data D a where MkD :: C a b => (a->Int->a) -> D a }}} That `b` can only be existential, which isn't at all what we want. So perhaps we want this {{{ class Back k1 (FrontBack k1 k t) => Front k k1 (t :: k) where ... }}} That makes more sense. (What is instead happening today is that the `k1` is being defaulted to `Any`.) But that too is problematic. Suppose there was a class-op: {{{ class Back k1 (FrontBack k1 k t) => Front k k1 (t :: k) where type family FrontBack k (t :: k) :: k1 op :: Proxy k t -> Int }}} Now the type of `op` is rather ambiguous {{{ op :: forall k k1 (t::k). Front k k1 t => Proxy k t -> Int }}} So nothing fixes `k1, so it'll be difficult to discharge the `Front` contraint from any givens. So simply addind kind variables from the superclass constraints isn't going to work. But defaulting them isn't very good either. Maybe we should complain about the unresolved kind variables in the class decl? The real problem is that `Back` is too polymorphic. If it had kind `k -> k` we'd probably be fine. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 12 23:35:38 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 12 Jun 2017 23:35:38 -0000 Subject: [GHC] #13739: Very slow linking of profiled executables In-Reply-To: <043.2d2650cd128632597774b5afb6c7a225@haskell.org> References: <043.2d2650cd128632597774b5afb6c7a225@haskell.org> Message-ID: <058.540d8031ae2be8153326285d97a1cb78@haskell.org> #13739: Very slow linking of profiled executables -------------------------------------+------------------------------------- Reporter: duog | Owner: (none) Type: bug | Status: new Priority: high | Milestone: 8.2.1 Component: Compiler | Version: 8.2.1-rc2 Resolution: | Keywords: Operating System: Linux | Architecture: x86_64 Type of failure: Compile-time | (amd64) performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by duog): I've attached timings with 3 versions of ld obtained from [http://ftp.gnu.org/gnu/binutils/]. These show that 2.27 fixes the issue we're running into. Still much slower than 8.0.2 though. I would also note that I find the very large file sizes of 8.2.1-no-gc- sections relative to 8.0.2 in comment 17 weird. It looks, to my untrained eye, like many more .o files from the archives are getting pulled in. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 12 23:38:09 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 12 Jun 2017 23:38:09 -0000 Subject: [GHC] #13819: TypeApplications-related GHC panic In-Reply-To: <051.cbfd374163652d5209657cd86d4948f0@haskell.org> References: <051.cbfd374163652d5209657cd86d4948f0@haskell.org> Message-ID: <066.9aabc9d7eacb82b3ad31078050b2255f@haskell.org> #13819: TypeApplications-related GHC panic -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: bug | Status: new Priority: high | Milestone: 8.2.1 Component: Compiler (Type | Version: 8.2.1-rc2 checker) | Keywords: Resolution: | TypeApplications Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * cc: bgamari (added) Comment: FWIW, commit b207b536ded40156f9adb168565ca78e1eef2c74 (`Generalize kind of the (->) tycon`) is what introduced this regression. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 12 23:38:28 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 12 Jun 2017 23:38:28 -0000 Subject: [GHC] #13773: Types are not normalized in instance declarations In-Reply-To: <047.b99d4e95d0428b43aa3236e584c6e7ac@haskell.org> References: <047.b99d4e95d0428b43aa3236e584c6e7ac@haskell.org> Message-ID: <062.a6666cd5ad72cd372f956b37beb02f3e@haskell.org> #13773: Types are not normalized in instance declarations -------------------------------------+------------------------------------- Reporter: augustss | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): It's a bit simpler than I realised. I think you are asking * That in any type pattern, the compiler should fully normalise * And then complain if any type functions remain * The evidence from this normalisation can be complete discarded. So {{{ type instance F (G Int) = blah }}} would normalise `(G Int)` to (say) `Tree [Bool]`, and then behave exactly as if you'd written {{{ type instance F (Tree [Bool]) = blah }}} If we later tried to solve a constraint involving `F (G Int)` we'd reduce the `G Int` to `Tree [Boo]]` and then (and only then) see the match with the `type instance`. I suppose that'd be straightforward, and clearly backward compatible. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 12 23:45:44 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 12 Jun 2017 23:45:44 -0000 Subject: [GHC] #13772: Cannot put HasCallStack on instances In-Reply-To: <047.d360e3ed5517211c4a279da62bac67fe@haskell.org> References: <047.d360e3ed5517211c4a279da62bac67fe@haskell.org> Message-ID: <062.4ea838779759990e43faa1a055e7d53b@haskell.org> #13772: Cannot put HasCallStack on instances -------------------------------------+------------------------------------- Reporter: augustss | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): {{{ foo :: Monoid a => (a,a) foo = (mempty, mempty) bar :: Tree a bar = fst foo }}} You say you want a `HasCallStack` constraint just on the `Tree` instance of `mempty`. But I don't think you can do that. The call site of `mempty` is in `foo`, which is polymorhpic, works for any instance. Only in `bar` do we beome specific to the `Tree` instance. It'd be fine if you wanted to say {{{ class Monoid a where mempty :: HasCallStack => a ... }}} but I doubt you do. I don't see how to achieve what you want. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 12 23:47:46 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 12 Jun 2017 23:47:46 -0000 Subject: [GHC] #13804: MonoLocalBinds/RankNTypes type inference regression in GHC 8.2 In-Reply-To: <050.b9855b85679e008576846333f1b379f9@haskell.org> References: <050.b9855b85679e008576846333f1b379f9@haskell.org> Message-ID: <065.01b1591fc9dd582e3e85098c822fde68@haskell.org> #13804: MonoLocalBinds/RankNTypes type inference regression in GHC 8.2 -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: highest | Milestone: Component: Compiler (Type | Version: 8.2.1-rc2 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: #11698 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * Attachment "T13804.patch" added. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 12 23:48:16 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 12 Jun 2017 23:48:16 -0000 Subject: [GHC] #13814: Unable to resolve instance for polykinded superclass constraint on associated-type-family. In-Reply-To: <048.9b1676217a0776f27637f0af7f65030e@haskell.org> References: <048.9b1676217a0776f27637f0af7f65030e@haskell.org> Message-ID: <063.a9a8381c7c39ce9c5ee9de65a7355270@haskell.org> #13814: Unable to resolve instance for polykinded superclass constraint on associated-type-family. -------------------------------------+------------------------------------- Reporter: isovector | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: polykinds, | type families Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): Replying to [comment:3 simonpj]: > The real problem is that `Back` is too polymorphic. If it had kind `k -> k` we'd probably be fine. Ah, you're right. This program //does// typecheck, as expected: {{{#!hs {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE PolyKinds #-} {-# LANGUAGE TypeFamilies #-} module Test where class Back t class Back (FrontBack t) => Front t where type FrontBack (t :: k) :: k instance Back Bool instance Front Int where type FrontBack Int = Bool }}} > Maybe we should complain about the unresolved kind variables in the class decl? That sounds like a good approach, yes. The error message might be confusing since it mentions an inferred kind variable, but I'd argue that that error would be far clearer than the current one, which is rather enigmatic. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 12 23:48:55 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 12 Jun 2017 23:48:55 -0000 Subject: [GHC] #13804: MonoLocalBinds/RankNTypes type inference regression in GHC 8.2 In-Reply-To: <050.b9855b85679e008576846333f1b379f9@haskell.org> References: <050.b9855b85679e008576846333f1b379f9@haskell.org> Message-ID: <065.2dd6523878b10ebcc933303e2326c1c2@haskell.org> #13804: MonoLocalBinds/RankNTypes type inference regression in GHC 8.2 -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: highest | Milestone: Component: Compiler (Type | Version: 8.2.1-rc2 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: #11698 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): The attached patch does the job, but regresses `perf/compiler/T12227`. I'm tied up this week; would anyone like to investigate? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jun 13 00:05:25 2017 From: ghc-devs at haskell.org (GHC) Date: Tue, 13 Jun 2017 00:05:25 -0000 Subject: [GHC] #13541: Make it easier to use the gold linker In-Reply-To: <046.0b1321a637ed3292c60514e6510d2c09@haskell.org> References: <046.0b1321a637ed3292c60514e6510d2c09@haskell.org> Message-ID: <061.17edcd2963c925f2eeeadb6ad42a0a95@haskell.org> #13541: Make it easier to use the gold linker -------------------------------------+------------------------------------- Reporter: bgamari | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * cc: RyanGlScott (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jun 13 00:11:21 2017 From: ghc-devs at haskell.org (GHC) Date: Tue, 13 Jun 2017 00:11:21 -0000 Subject: [GHC] #13773: Types are not normalized in instance declarations In-Reply-To: <047.b99d4e95d0428b43aa3236e584c6e7ac@haskell.org> References: <047.b99d4e95d0428b43aa3236e584c6e7ac@haskell.org> Message-ID: <062.3d67ff3d45d39402c1e87c88d562f465@haskell.org> #13773: Types are not normalized in instance declarations -------------------------------------+------------------------------------- Reporter: augustss | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Iceland_jack): Has anyone encountered more complex uses for this feature? Does it interact differently with injective families? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jun 13 00:22:48 2017 From: ghc-devs at haskell.org (GHC) Date: Tue, 13 Jun 2017 00:22:48 -0000 Subject: [GHC] #13791: Document allowed syntax in WARNING and DEPRECATED pragmas In-Reply-To: <046.d7785f3c9a9f9afccfdc542d40ba4787@haskell.org> References: <046.d7785f3c9a9f9afccfdc542d40ba4787@haskell.org> Message-ID: <061.7b9d810ed41424031d7716718ddf1767@haskell.org> #13791: Document allowed syntax in WARNING and DEPRECATED pragmas -------------------------------------+------------------------------------- Reporter: phischu | Owner: (none) Type: bug | Status: new Priority: lowest | Milestone: Component: Compiler | Version: 8.0.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Documentation | Unknown/Multiple bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"8f72608953fee7ff77a6d89b00f25749261b8820/ghc" 8f72608/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="8f72608953fee7ff77a6d89b00f25749261b8820" users-guide: Document multi-line DEPRECATED pragmas Fixes #13791. [skip ci] Test Plan: Read it Reviewers: austin Subscribers: rwbarton, thomie GHC Trac Issues: #13791 Differential Revision: https://phabricator.haskell.org/D3639 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jun 13 00:22:48 2017 From: ghc-devs at haskell.org (GHC) Date: Tue, 13 Jun 2017 00:22:48 -0000 Subject: [GHC] #13807: GHC 8.2 nondeterministic with foreign imports In-Reply-To: <046.b74945b333405c65044cabd09b1ff21f@haskell.org> References: <046.b74945b333405c65044cabd09b1ff21f@haskell.org> Message-ID: <061.0d52f2f10fe514a412a1ecf6a2ff0209@haskell.org> #13807: GHC 8.2 nondeterministic with foreign imports -------------------------------------+------------------------------------- Reporter: niteria | Owner: niteria Type: bug | Status: new Priority: high | Milestone: Component: Compiler | Version: 8.2.1-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"dcdc391609d6ff902989d806266855901c051608/ghc" dcdc3916/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="dcdc391609d6ff902989d806266855901c051608" Fix #13807 - foreign import nondeterminism The problem was that the generated label included a freshly assigned Unique value. Test Plan: Added a new test and looked at the generated stub: ``` #include "HsFFI.h" #ifdef __cplusplus extern "C" { #endif extern HsInt zdmainzdAzdAzuzzlzzgzzg(StgStablePtr the_stableptr); extern HsInt zdmainzdAzdAzumkStringWriter(StgStablePtr the_stableptr); #ifdef __cplusplus } #endif ``` ./validate Reviewers: simonmar, austin, bgamari Reviewed By: simonmar Subscribers: rwbarton, thomie GHC Trac Issues: #13807 Differential Revision: https://phabricator.haskell.org/D3633 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jun 13 00:22:48 2017 From: ghc-devs at haskell.org (GHC) Date: Tue, 13 Jun 2017 00:22:48 -0000 Subject: [GHC] #12545: Compilation time/space regression in GHC 8.0/8.1 (search in type-level lists and -O) In-Reply-To: <057.9aecaec89b7fd255565e55bac0801cc6@haskell.org> References: <057.9aecaec89b7fd255565e55bac0801cc6@haskell.org> Message-ID: <072.2667192847473177517a1a51a9b60042@haskell.org> #12545: Compilation time/space regression in GHC 8.0/8.1 (search in type-level lists and -O) -------------------------------------+------------------------------------- Reporter: | Owner: (none) mikhail.vorozhtsov | Type: bug | Status: patch Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Inlining Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3632 Wiki Page: | -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"6ddb3aaf5265d15a422dbaeb5396c2c20acc9ff1/ghc" 6ddb3aaf/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="6ddb3aaf5265d15a422dbaeb5396c2c20acc9ff1" Add perf test for #12545 Commit 2b74bd9d8b4c6b20f3e8d9ada12e7db645cc3c19 did wonders for the program reported in #12545. Let's add a perf test for it to make sure it stays fast. Test Plan: make test TEST=T12545 Reviewers: austin, bgamari Reviewed By: bgamari Subscribers: rwbarton, thomie GHC Trac Issues: #12545 Differential Revision: https://phabricator.haskell.org/D3632 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jun 13 00:22:48 2017 From: ghc-devs at haskell.org (GHC) Date: Tue, 13 Jun 2017 00:22:48 -0000 Subject: [GHC] #13781: (a :: (k :: Type)) is too exotic for Template Haskell In-Reply-To: <050.7f27300750c1a83b8949d3702d68d5eb@haskell.org> References: <050.7f27300750c1a83b8949d3702d68d5eb@haskell.org> Message-ID: <065.44715976435f868cb36ffec93a218176@haskell.org> #13781: (a :: (k :: Type)) is too exotic for Template Haskell -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: RyanGlScott Type: bug | Status: patch Priority: normal | Milestone: Component: Template Haskell | Version: 8.0.1 Resolution: | Keywords: TypeInType Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3627 Wiki Page: | -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"9a3ca8deb43626c2aee10eddc029880cd2c4b4da/ghc" 9a3ca8de/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="9a3ca8deb43626c2aee10eddc029880cd2c4b4da" Support signatures at the kind level in Template Haskell `repNonArrowKind` was missing a case for `HsKindSig`, which this commit adds. Fixes #13781. Test Plan: make test TEST=T13781 Reviewers: goldfire, austin, bgamari Reviewed By: goldfire Subscribers: rwbarton, thomie GHC Trac Issues: #13781 Differential Revision: https://phabricator.haskell.org/D3627 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jun 13 00:22:48 2017 From: ghc-devs at haskell.org (GHC) Date: Tue, 13 Jun 2017 00:22:48 -0000 Subject: [GHC] #13426: compile-time memory-usage regression for DynFlags between GHC 8.0 and GHC 8.2 In-Reply-To: <042.588059ee1290b666bd7f0947c071e1ff@haskell.org> References: <042.588059ee1290b666bd7f0947c071e1ff@haskell.org> Message-ID: <057.a586243ec657f75f221fd545140b7109@haskell.org> #13426: compile-time memory-usage regression for DynFlags between GHC 8.0 and GHC 8.2 -------------------------------------+------------------------------------- Reporter: hvr | Owner: (none) Type: bug | Status: new Priority: high | Milestone: 8.2.1 Component: Compiler | Version: 8.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3399, Wiki Page: | Phab:D3400, Phab:D3421 -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"2088d0be17dccfa91a4759bdbb20faae77c8dbed/ghc" 2088d0be/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="2088d0be17dccfa91a4759bdbb20faae77c8dbed" Stop forcing everything in coreBindsSize `coreBindsSize` forced a ton of structure to stop space leaks. Reid Barton has done some work recently to try to stop the leaks at their source instead. Memory residency remains well below the numbers Herbert posted on #13426 originally, but in some cases a ways above the ones from 8.0. I need to figure out how to get the numbers matched up to individual modules and do some profiling. Relates to #13426 Reviewers: austin, bgamari Reviewed By: bgamari Subscribers: rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D3606 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jun 13 00:22:48 2017 From: ghc-devs at haskell.org (GHC) Date: Tue, 13 Jun 2017 00:22:48 -0000 Subject: [GHC] #12056: Too aggressive `-w` option In-Reply-To: <042.615977cbd760a0223c1133d5e2a0fac1@haskell.org> References: <042.615977cbd760a0223c1133d5e2a0fac1@haskell.org> Message-ID: <057.ba49a8fe9f112bf96f961a26f3fcb7fa@haskell.org> #12056: Too aggressive `-w` option -------------------------------------+------------------------------------- Reporter: asr | Owner: (none) Type: bug | Status: patch Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: #11429, #11789 | Differential Rev(s): Phab:D3581 Wiki Page: | -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"af9612bf862daaa99384eefa3059054053ecbee8/ghc" af9612b/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="af9612bf862daaa99384eefa3059054053ecbee8" Make -w less aggressive (Trac #12056) Previously -w combined with -Wunrecognised-warning-flags would not report unrecognized flags. Reviewers: austin, bgamari, dfeuer Reviewed By: bgamari Subscribers: dfeuer, rwbarton, thomie GHC Trac Issues: #12056 Differential Revision: https://phabricator.haskell.org/D3581 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jun 13 00:24:14 2017 From: ghc-devs at haskell.org (GHC) Date: Tue, 13 Jun 2017 00:24:14 -0000 Subject: [GHC] #13791: Document allowed syntax in WARNING and DEPRECATED pragmas In-Reply-To: <046.d7785f3c9a9f9afccfdc542d40ba4787@haskell.org> References: <046.d7785f3c9a9f9afccfdc542d40ba4787@haskell.org> Message-ID: <061.26a624a2a98677c29fb8e5a2327c5a88@haskell.org> #13791: Document allowed syntax in WARNING and DEPRECATED pragmas -------------------------------------+------------------------------------- Reporter: phischu | Owner: (none) Type: bug | Status: closed Priority: lowest | Milestone: 8.2.1 Component: Compiler | Version: 8.0.2 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Documentation | Unknown/Multiple bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => closed * resolution: => fixed * milestone: => 8.2.1 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jun 13 00:25:13 2017 From: ghc-devs at haskell.org (GHC) Date: Tue, 13 Jun 2017 00:25:13 -0000 Subject: [GHC] #13807: GHC 8.2 nondeterministic with foreign imports In-Reply-To: <046.b74945b333405c65044cabd09b1ff21f@haskell.org> References: <046.b74945b333405c65044cabd09b1ff21f@haskell.org> Message-ID: <061.748344d0f8938a3e154786a8c2b413b3@haskell.org> #13807: GHC 8.2 nondeterministic with foreign imports -------------------------------------+------------------------------------- Reporter: niteria | Owner: niteria Type: bug | Status: merge Priority: high | Milestone: 8.2.1 Component: Compiler | Version: 8.2.1-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => merge * milestone: => 8.2.1 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jun 13 00:26:32 2017 From: ghc-devs at haskell.org (GHC) Date: Tue, 13 Jun 2017 00:26:32 -0000 Subject: [GHC] #12545: Compilation time/space regression in GHC 8.0/8.1 (search in type-level lists and -O) In-Reply-To: <057.9aecaec89b7fd255565e55bac0801cc6@haskell.org> References: <057.9aecaec89b7fd255565e55bac0801cc6@haskell.org> Message-ID: <072.cc924beb6ddf82061f8c227ee338b576@haskell.org> #12545: Compilation time/space regression in GHC 8.0/8.1 (search in type-level lists and -O) -------------------------------------+------------------------------------- Reporter: | Owner: (none) mikhail.vorozhtsov | Type: bug | Status: closed Priority: normal | Milestone: 8.2.1 Component: Compiler | Version: 8.0.1 Resolution: fixed | Keywords: Inlining Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Compile-time | Test Case: performance bug | perf/compiler/T12545 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3632 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: patch => closed * testcase: => perf/compiler/T12545 * resolution: => fixed * milestone: => 8.2.1 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jun 13 00:27:18 2017 From: ghc-devs at haskell.org (GHC) Date: Tue, 13 Jun 2017 00:27:18 -0000 Subject: [GHC] #13781: (a :: (k :: Type)) is too exotic for Template Haskell In-Reply-To: <050.7f27300750c1a83b8949d3702d68d5eb@haskell.org> References: <050.7f27300750c1a83b8949d3702d68d5eb@haskell.org> Message-ID: <065.159904e46c0ef61a5cbd92c0cc287280@haskell.org> #13781: (a :: (k :: Type)) is too exotic for Template Haskell -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: RyanGlScott Type: bug | Status: closed Priority: normal | Milestone: 8.4.1 Component: Template Haskell | Version: 8.0.1 Resolution: fixed | Keywords: TypeInType Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3627 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: patch => closed * resolution: => fixed * milestone: => 8.4.1 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jun 13 00:27:39 2017 From: ghc-devs at haskell.org (GHC) Date: Tue, 13 Jun 2017 00:27:39 -0000 Subject: [GHC] #13781: (a :: (k :: Type)) is too exotic for Template Haskell In-Reply-To: <050.7f27300750c1a83b8949d3702d68d5eb@haskell.org> References: <050.7f27300750c1a83b8949d3702d68d5eb@haskell.org> Message-ID: <065.75d0fad8c92b78bbe5f9b89943e04cb1@haskell.org> #13781: (a :: (k :: Type)) is too exotic for Template Haskell -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: RyanGlScott Type: bug | Status: closed Priority: normal | Milestone: 8.4.1 Component: Template Haskell | Version: 8.0.1 Resolution: fixed | Keywords: TypeInType Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: T13781 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3627 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * testcase: => T13781 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jun 13 00:28:26 2017 From: ghc-devs at haskell.org (GHC) Date: Tue, 13 Jun 2017 00:28:26 -0000 Subject: [GHC] #12056: Too aggressive `-w` option In-Reply-To: <042.615977cbd760a0223c1133d5e2a0fac1@haskell.org> References: <042.615977cbd760a0223c1133d5e2a0fac1@haskell.org> Message-ID: <057.a4b6ca5fcb3d5a870319adaf524af7d8@haskell.org> #12056: Too aggressive `-w` option -------------------------------------+------------------------------------- Reporter: asr | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.4.1 Component: Compiler | Version: 8.0.1 Resolution: fixed | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: #11429, #11789 | Differential Rev(s): Phab:D3581 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: patch => closed * resolution: => fixed * milestone: => 8.4.1 Comment: I don't think this is critical for 8.2, but do yell if you disagree. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jun 13 00:36:57 2017 From: ghc-devs at haskell.org (GHC) Date: Tue, 13 Jun 2017 00:36:57 -0000 Subject: [GHC] #13541: Make it easier to use the gold linker In-Reply-To: <046.0b1321a637ed3292c60514e6510d2c09@haskell.org> References: <046.0b1321a637ed3292c60514e6510d2c09@haskell.org> Message-ID: <061.acba8ec761deb95fc02e78f541dc4dac@haskell.org> #13541: Make it easier to use the gold linker -------------------------------------+------------------------------------- Reporter: bgamari | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by duog): * cc: duog (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jun 13 01:24:07 2017 From: ghc-devs at haskell.org (GHC) Date: Tue, 13 Jun 2017 01:24:07 -0000 Subject: [GHC] #13821: bindings for unlifted types are allowed in .hs-boot files and .hsig files Message-ID: <043.23e5a07809642797cc00f131ea2af984@haskell.org> #13821: bindings for unlifted types are allowed in .hs-boot files and .hsig files -------------------------------------+------------------------------------- Reporter: duog | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.1-rc2 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: GHC accepts Unknown/Multiple | invalid program Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- The following module compiles without error. {{{ A.hs-boot --------- {-# LANGUAGE MagicHash -#} module A where import GHC.Prim x :: Int# === ghc -c A.hs-boot }}} I would expect to get a "Top-level unlifted bindings are not allowed." error, as I would with a .hs module. Similarly {{{ A.hsig ====== {-# LANGUAGE MagicHash #-} unit U where signature A where import GHC.Prim x :: Int# === ghc --backpack -fno-code -fwrite-interface A.hsig }}} succeeds, where I would expect the same error. This error is thrown during desugaring, and .hs-boot and .hsig files are not desugared. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jun 13 01:51:16 2017 From: ghc-devs at haskell.org (GHC) Date: Tue, 13 Jun 2017 01:51:16 -0000 Subject: [GHC] #13772: Cannot put HasCallStack on instances In-Reply-To: <047.d360e3ed5517211c4a279da62bac67fe@haskell.org> References: <047.d360e3ed5517211c4a279da62bac67fe@haskell.org> Message-ID: <062.284bb90ff6f42d5c9567fe823597afbf@haskell.org> #13772: Cannot put HasCallStack on instances -------------------------------------+------------------------------------- Reporter: augustss | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Iceland_jack): I am not very familiar with `HasCallStack` but it is possible to go from `ImplicitParams` to kmett's reflection library, I don't know where you would call [https://hackage.haskell.org/package/reflection-2.1.2/docs /Data-Reflection.html#v:reify reify] but it may help: {{{#!hs import Data.Proxy import GHC.Stack import Data.Reflection import Data.Monoid hiding ((<>)) import Data.Semigroup newtype WithClassStack s a = WCS a instance Semigroup a => Semigroup (WithClassStack s a) where WCS a <> WCS b = WCS (a <> b) instance (Semigroup a, Reifies s CallStack) => Monoid (WithClassStack s a) where mempty = error "No mempty!" where ?callStack = reflect (Proxy @s) mappend = (<>) }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jun 13 02:55:10 2017 From: ghc-devs at haskell.org (GHC) Date: Tue, 13 Jun 2017 02:55:10 -0000 Subject: [GHC] #2600: Bind type variables in RULES In-Reply-To: <046.60d3c1925e5a0ef8b7d1f9b2b5ebeabc@haskell.org> References: <046.60d3c1925e5a0ef8b7d1f9b2b5ebeabc@haskell.org> Message-ID: <061.3424e462f4157ef55d73e59d0965ba13@haskell.org> #2600: Bind type variables in RULES -------------------------------------+------------------------------------- Reporter: simonpj | Owner: simonpj Type: feature request | Status: new Priority: lowest | Milestone: Component: Compiler | Version: 6.8.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #2110 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by goldfire): Ideas to fix this are in [https://github.com/ghc-proposals/ghc- proposals/pull/55 this recent proposal]. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jun 13 04:50:58 2017 From: ghc-devs at haskell.org (GHC) Date: Tue, 13 Jun 2017 04:50:58 -0000 Subject: [GHC] #13587: addTopDecls fails with typed Template Haskell In-Reply-To: <048.1e9cb82827e3acfaa8c4e1f0f4c12487@haskell.org> References: <048.1e9cb82827e3acfaa8c4e1f0f4c12487@haskell.org> Message-ID: <063.019c66fbedcb52588f306c04c6527a04@haskell.org> #13587: addTopDecls fails with typed Template Haskell -------------------------------------+------------------------------------- Reporter: tmcdonell | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 8.2.1-rc1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by tmcdonell): Any new information on this one? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jun 13 08:14:12 2017 From: ghc-devs at haskell.org (GHC) Date: Tue, 13 Jun 2017 08:14:12 -0000 Subject: [GHC] #13810: Gold linker fails In-Reply-To: <045.174b108f34b20d346eba46d31b44114b@haskell.org> References: <045.174b108f34b20d346eba46d31b44114b@haskell.org> Message-ID: <060.634c695c565cc33466f8ad3a153789c6@haskell.org> #13810: Gold linker fails ---------------------------------+---------------------------------------- Reporter: ksaric | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: linker Operating System: Linux | Architecture: Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | ---------------------------------+---------------------------------------- Changes (by domenkozar): * cc: domen.kozar@… (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jun 13 08:22:01 2017 From: ghc-devs at haskell.org (GHC) Date: Tue, 13 Jun 2017 08:22:01 -0000 Subject: [GHC] #13426: compile-time memory-usage regression for DynFlags between GHC 8.0 and GHC 8.2 In-Reply-To: <042.588059ee1290b666bd7f0947c071e1ff@haskell.org> References: <042.588059ee1290b666bd7f0947c071e1ff@haskell.org> Message-ID: <057.851215744aac65492f7aeed714a608ec@haskell.org> #13426: compile-time memory-usage regression for DynFlags between GHC 8.0 and GHC 8.2 -------------------------------------+------------------------------------- Reporter: hvr | Owner: (none) Type: bug | Status: new Priority: high | Milestone: 8.2.1 Component: Compiler | Version: 8.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3399, Wiki Page: | Phab:D3400, Phab:D3421 -------------------------------------+------------------------------------- Comment (by simonpj): Hang on > in some cases a ways above the ones from 8.0. But I see no changes in the tessuite in this patch. So what regressed? Or, were all the regressions relative to 8.0, and had already been accepted for 8.2? Which cases in particular regressed wrt 8.0? "Some cases" isn't very explicit! Did removing the `coreBindsSize` improve compiler speed (slightly) becuase of doing less work? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jun 13 08:54:32 2017 From: ghc-devs at haskell.org (GHC) Date: Tue, 13 Jun 2017 08:54:32 -0000 Subject: [GHC] #13810: Gold linker fails In-Reply-To: <045.174b108f34b20d346eba46d31b44114b@haskell.org> References: <045.174b108f34b20d346eba46d31b44114b@haskell.org> Message-ID: <060.67403f9ce01c65c419084d36f4545dab@haskell.org> #13810: Gold linker fails ---------------------------------+---------------------------------------- Reporter: ksaric | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: linker Operating System: Linux | Architecture: Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | ---------------------------------+---------------------------------------- Changes (by nh2): * cc: nh2 (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jun 13 10:51:28 2017 From: ghc-devs at haskell.org (GHC) Date: Tue, 13 Jun 2017 10:51:28 -0000 Subject: [GHC] #13820: GHC goes out of memory while compiling nothing In-Reply-To: <045.02f4d99bdc465f78bea41f2d527be881@haskell.org> References: <045.02f4d99bdc465f78bea41f2d527be881@haskell.org> Message-ID: <060.86e276d87e7f5da0197a160dbc59f839@haskell.org> #13820: GHC goes out of memory while compiling nothing -------------------------------------+------------------------------------- Reporter: seunje | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by seunje): Segfaults on Linux x64 with 8GB memory, no swap file. It works (n=27) on 16GB OSX machine, peeking at 11GB. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jun 13 12:44:47 2017 From: ghc-devs at haskell.org (GHC) Date: Tue, 13 Jun 2017 12:44:47 -0000 Subject: [GHC] #10843: Allow do blocks without dollar signs as arguments In-Reply-To: <049.979a39a09d7a881598f53a6a6ce9bbe3@haskell.org> References: <049.979a39a09d7a881598f53a6a6ce9bbe3@haskell.org> Message-ID: <064.0b8b1c119ae07bc83f1564827857e5b1@haskell.org> #10843: Allow do blocks without dollar signs as arguments -------------------------------------+------------------------------------- Reporter: agibiansky | Owner: agibiansky Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.2 (Parser) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #11706 | Differential Rev(s): Phab:D1219 Wiki Page: | -------------------------------------+------------------------------------- Changes (by mentheta): * cc: mentheta (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jun 13 13:40:12 2017 From: ghc-devs at haskell.org (GHC) Date: Tue, 13 Jun 2017 13:40:12 -0000 Subject: [GHC] #13793: Simple program trips checkNurserySanity() In-Reply-To: <046.a36b0da0c049dac7c618bbfdc92da5ef@haskell.org> References: <046.a36b0da0c049dac7c618bbfdc92da5ef@haskell.org> Message-ID: <061.8c399926e90c053edf1aa876da54f830@haskell.org> #13793: Simple program trips checkNurserySanity() -------------------------------------+------------------------------------- Reporter: niteria | Owner: niteria Type: bug | Status: new Priority: normal | Milestone: Component: Runtime System | Version: 8.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: x86_64 | (amd64) Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): No no, I was just making sure this wasn't dropped. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jun 13 14:19:26 2017 From: ghc-devs at haskell.org (GHC) Date: Tue, 13 Jun 2017 14:19:26 -0000 Subject: [GHC] #13822: GHC not using injectivity? Message-ID: <051.2a3d251c10227c1a71de0d444bf548f8@haskell.org> #13822: GHC not using injectivity? -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Keywords: | Operating System: Unknown/Multiple InjectiveFamilies, TypeInType | Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- This may be normal behavior but.. (Example from [http://repository.brynmawr.edu/cgi/viewcontent.cgi?article=1014&context=compsci_pubs System FC with Explicit Kind Equality]) {{{#!hs {-# LANGUAGE GADTs, TypeOperators, PolyKinds, DataKinds, TypeFamilyDependencies, TypeInType, RankNTypes, LambdaCase, EmptyCase #-} import Data.Kind data KIND = STAR | KIND :> KIND data Ty :: KIND -> Type where TInt :: Ty STAR TBool :: Ty STAR TMaybe :: Ty (STAR :> STAR) TApp :: Ty (a :> b) -> (Ty a -> Ty b) type family IK (k :: KIND) = (res :: Type) | res -> k where IK STAR = Type IK (a:>b) = IK a -> IK b type family I (t :: Ty k) = (res :: IK k) | res -> t where I TInt = Int I TBool = Bool I TMaybe = Maybe I (TApp f a) = (I f) (I a) data TyRep (k :: KIND) (t :: Ty k) where TyInt :: TyRep STAR TInt TyBool :: TyRep STAR TBool TyMaybe :: TyRep (STAR:>STAR) TMaybe TyApp :: TyRep (a:>b) f -> TyRep a x -> TyRep b (TApp f x) zero :: TyRep STAR a -> I a zero = \case TyInt -> 0 TyBool -> False TyApp TyMaybe _ -> Nothing }}} When I ask it to infer the representation for `Int` and `Bool` it does so with no surprises {{{#!hs -- Inferred type: -- -- int :: TyRep STAR TInt -> Int int rep = zero rep :: Int -- bool:: TyRep STAR TBool -> Bool bool rep = zero rep :: Bool }}} but inferring the representation for `Maybe Int` fails {{{#!hs -- v.hs:43:16: error: -- • Couldn't match kind ‘k’ with ‘'STAR’ -- ‘k’ is a rigid type variable bound by -- the inferred type of -- maybeInt :: (I 'TInt ~ Int, I 'TMaybe ~ Maybe) => -- TyRep 'STAR ('TApp 'TMaybe 'TInt) -> Maybe Int -- at v.hs:25:3 -- When matching the kind of ‘'TMaybe’ -- Expected type: Maybe Int -- Actual type: I ('TApp 'TMaybe 'TInt) -- • In the expression: zero rep :: Maybe Int -- In an equation for ‘maybeInt’: maybeInt rep = zero rep :: Maybe Int -- • Relevant bindings include -- rep :: TyRep 'STAR ('TApp 'TMaybe 'TInt) (bound at v.hs:43:10) -- maybeInt :: TyRep 'STAR ('TApp 'TMaybe 'TInt) -> Maybe Int -- (bound at v.hs:43:1) -- Failed, modules loaded: none. maybeInt rep = zero rep :: Maybe Int }}} even though `I` is injective and GHC knows that `I (TMaybe `TApp` TMaybe) = Maybe Int` {{{ >>> :kind! I (TMaybe `TApp` TInt) I (TMaybe `TApp` TInt) :: IK 'STAR = Maybe Int }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jun 13 14:31:26 2017 From: ghc-devs at haskell.org (GHC) Date: Tue, 13 Jun 2017 14:31:26 -0000 Subject: [GHC] #13822: GHC not using injectivity? In-Reply-To: <051.2a3d251c10227c1a71de0d444bf548f8@haskell.org> References: <051.2a3d251c10227c1a71de0d444bf548f8@haskell.org> Message-ID: <066.003aaae27e0c703e12d637246ed27ee1@haskell.org> #13822: GHC not using injectivity? -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: | InjectiveFamilies, TypeInType Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Iceland_jack): Output I do not understand, with explicit kinds / coercions {{{ /tmp/v.hs:41:16: error: • Couldn't match kind ‘k’ with ‘'STAR’ ‘k’ is a rigid type variable bound by the inferred type of maybeInt :: ((I 'STAR ('TInt |> Sym (Ty U(hole:{a2uB}, k1, 'STAR)_N)_N) :: IK * 'STAR) ~~ ((Int |> Sym Main.D:R:IK[0]) :: IK * 'STAR), (I ('STAR ':> 'STAR) ('TMaybe |> Sym (Ty (U(hole:{a2uB}, k1, 'STAR)_N ':> U(hole:{a2uC}, k, 'STAR)_N)_N)_N) :: IK * ('STAR ':> 'STAR)) ~~ ((Maybe |> Sym (Main.D:R:IK[1] <'STAR>_N <'STAR>_N ; Sym (Sym Main.D:R:IK[0] -> Sym Main.D:R:IK[0]))) :: IK * ('STAR ':> 'STAR))) => TyRep 'STAR ('TApp 'STAR 'STAR ('TMaybe |> Sym (Ty (U(hole:{a2uB}, k1, 'STAR)_N ':> U(hole:{a2uC}, k, 'STAR)_N)_N)_N) ('TInt |> Sym (Ty U(hole:{a2uB}, k1, 'STAR)_N)_N)) -> Maybe Int at /tmp/v.hs:23:3 When matching types ('TMaybe |> Sym (Ty (U(hole:{a2uB}, k1, 'STAR)_N ':> U(hole:{a2uC}, k, 'STAR)_N)_N)_N) :: Ty (k1 ':> k) 'TMaybe :: Ty ('STAR ':> 'STAR) Expected type: Maybe Int Actual type: (I 'STAR ('TApp 'STAR 'STAR ('TMaybe |> Sym (Ty (U(hole:{a2uB}, k1, 'STAR)_N ':> U(hole:{a2uC}, k, 'STAR)_N)_N)_N) ('TInt |> Sym (Ty U(hole:{a2uB}, k1, 'STAR)_N)_N)) |> Main.D:R:IK[0]) • In the expression: zero rep :: Maybe Int In an equation for ‘maybeInt’: maybeInt rep = zero rep :: Maybe Int • Relevant bindings include rep :: TyRep 'STAR ('TApp 'STAR 'STAR ('TMaybe |> Sym (Ty (U(hole:{a2uB}, k1, 'STAR)_N ':> U(hole:{a2uC}, k, 'STAR)_N)_N)_N) ('TInt |> Sym (Ty U(hole:{a2uB}, k1, 'STAR)_N)_N)) (bound at /tmp/v.hs:41:10) maybeInt :: TyRep 'STAR ('TApp 'STAR 'STAR ('TMaybe |> Sym (Ty (U(hole:{a2uB}, k1, 'STAR)_N ':> U(hole:{a2uC}, k, 'STAR)_N)_N)_N) ('TInt |> Sym (Ty U(hole:{a2uB}, k1, 'STAR)_N)_N)) -> Maybe Int (bound at /tmp/v.hs:41:1) Failed, modules loaded: none. }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jun 13 17:19:18 2017 From: ghc-devs at haskell.org (GHC) Date: Tue, 13 Jun 2017 17:19:18 -0000 Subject: [GHC] #13823: Use NonEmpty lists in more places in the GHC API Message-ID: <050.a056cb71c10cdfa479dac95f5ba89eb4@haskell.org> #13823: Use NonEmpty lists in more places in the GHC API -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: task | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.3 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: #8782 Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- After GHC 8.2 is released and we drop support for building GHC with 7.10, we should try to use `Data.List.NonEmpty` in more places in the GHC API. I ran into this issue recently when using some functions from `ListSetOps`: {{{#!hs removeDups :: (a -> a -> Ordering) -> [a] -> ([a], [[a]]) findDupsEq :: (a -> a -> Bool) -> [a] -> [[a]] equivClasses :: (a -> a -> Ordering) -> [a] -> [[a]] }}} These type signatures are terrible. Really, they should be: {{{#!hs removeDups :: (a -> a -> Ordering) -> [a] -> ([a], [NonEmpty a]) findDupsEq :: (a -> a -> Bool) -> [a] -> [NonEmpty a] equivClasses :: (a -> a -> Ordering) -> [a] -> [NonEmpty a] }}} Since 90% of the time, the first thing you do after finding duplicates is to take a representative from the duplicate set. With lists, this requires the partial operation `head`, but with `NonEmpty`, this can be total like it was intended to be. I'm sure there are other places in the API that could benefit from `NonEmpty`, so if you have any suggestions, please leave them here. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jun 13 17:19:32 2017 From: ghc-devs at haskell.org (GHC) Date: Tue, 13 Jun 2017 17:19:32 -0000 Subject: [GHC] #13823: Use NonEmpty lists in more places in the GHC API In-Reply-To: <050.a056cb71c10cdfa479dac95f5ba89eb4@haskell.org> References: <050.a056cb71c10cdfa479dac95f5ba89eb4@haskell.org> Message-ID: <065.4fd47b5b23d04c7877a969860cca9db6@haskell.org> #13823: Use NonEmpty lists in more places in the GHC API -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: RyanGlScott Type: task | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #8782 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * owner: (none) => RyanGlScott -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jun 13 17:28:51 2017 From: ghc-devs at haskell.org (GHC) Date: Tue, 13 Jun 2017 17:28:51 -0000 Subject: [GHC] #13823: Use NonEmpty lists in more places in the GHC API In-Reply-To: <050.a056cb71c10cdfa479dac95f5ba89eb4@haskell.org> References: <050.a056cb71c10cdfa479dac95f5ba89eb4@haskell.org> Message-ID: <065.8250c50af3448b81f5002ff021b01470@haskell.org> #13823: Use NonEmpty lists in more places in the GHC API -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: RyanGlScott Type: task | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #8782 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by mpickering): I've never found using `NonEmpty` to be worthwhile with Haskell's type system and in general I think we should be looking to remove `ListSetOps` rather than spending time making the API better. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jun 13 17:32:09 2017 From: ghc-devs at haskell.org (GHC) Date: Tue, 13 Jun 2017 17:32:09 -0000 Subject: [GHC] #13823: Use NonEmpty lists in more places in the GHC API In-Reply-To: <050.a056cb71c10cdfa479dac95f5ba89eb4@haskell.org> References: <050.a056cb71c10cdfa479dac95f5ba89eb4@haskell.org> Message-ID: <065.f67e309960e3d87d3887f6cdf613a92f@haskell.org> #13823: Use NonEmpty lists in more places in the GHC API -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: RyanGlScott Type: task | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #8782 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): Well, I'm looking to avoid partially retrieving the representative of a list of duplicates, by hook or by crook. Do you have an idea in mind for a better `ListSetOps` replacement? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jun 13 18:18:02 2017 From: ghc-devs at haskell.org (GHC) Date: Tue, 13 Jun 2017 18:18:02 -0000 Subject: [GHC] #13824: ghc 8.2 does not build for me on ppc64le Message-ID: <048.696afd9b4d70bfaf30354dc33faf7c20@haskell.org> #13824: ghc 8.2 does not build for me on ppc64le ---------------------------------+---------------------------------------- Reporter: msuchanek | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.1-rc2 Keywords: | Operating System: Linux Architecture: powerpc64 | Type of failure: Building GHC failed Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: ---------------------------------+---------------------------------------- [ 5732s] ghc-stage1: panic! (the 'impossible' happened) [ 5732s] (GHC version 8.2.0.20170613 for powerpc64le-unknown-linux): [ 5732s] dwarfReturnRegNo: Unsupported platform! [ 5732s] CallStack (from HasCallStack): [ 5732s] error, called at compiler/nativeGen/Dwarf/Constants.hs:225:19 in ghc:Dwarf.Constants [ 5732s] [ 5732s] Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jun 13 18:18:28 2017 From: ghc-devs at haskell.org (GHC) Date: Tue, 13 Jun 2017 18:18:28 -0000 Subject: [GHC] #13824: ghc 8.2 does not build for me on ppc64le In-Reply-To: <048.696afd9b4d70bfaf30354dc33faf7c20@haskell.org> References: <048.696afd9b4d70bfaf30354dc33faf7c20@haskell.org> Message-ID: <063.470ab0a276e94267682152c97f5fea3a@haskell.org> #13824: ghc 8.2 does not build for me on ppc64le ----------------------------------------+--------------------------------- Reporter: msuchanek | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.1-rc2 Resolution: | Keywords: Operating System: Linux | Architecture: powerpc64 Type of failure: Building GHC failed | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | ----------------------------------------+--------------------------------- Changes (by msuchanek): * Attachment "ghc82_log.txt.xz" added. full build log -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jun 13 19:16:15 2017 From: ghc-devs at haskell.org (GHC) Date: Tue, 13 Jun 2017 19:16:15 -0000 Subject: [GHC] #13824: ghc 8.2 does not build for me on ppc64le In-Reply-To: <048.696afd9b4d70bfaf30354dc33faf7c20@haskell.org> References: <048.696afd9b4d70bfaf30354dc33faf7c20@haskell.org> Message-ID: <063.60a86370a4725263e56a1b947bcdbb71@haskell.org> #13824: ghc 8.2 does not build for me on ppc64le ----------------------------------------+--------------------------------- Reporter: msuchanek | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.1-rc2 Resolution: | Keywords: Operating System: Linux | Architecture: powerpc64 Type of failure: Building GHC failed | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | ----------------------------------------+--------------------------------- @@ -0,0 +1,1 @@ + {{{ @@ -10,0 +11,1 @@ + }}} New description: {{{ [ 5732s] ghc-stage1: panic! (the 'impossible' happened) [ 5732s] (GHC version 8.2.0.20170613 for powerpc64le-unknown-linux): [ 5732s] dwarfReturnRegNo: Unsupported platform! [ 5732s] CallStack (from HasCallStack): [ 5732s] error, called at compiler/nativeGen/Dwarf/Constants.hs:225:19 in ghc:Dwarf.Constants [ 5732s] [ 5732s] Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug }}} -- Comment (by bgamari): Thanks for your report. It looks like you are building with `-g3`, which isn't supported on PowerPC. Is this present in `mk/build.mk`? There are a few ways we could deal with this: 1. Fail on unsupported platforms as we do now, perhaps with a nicer error message 2. Silently ignore the flag 3. Warn and ignore the flag -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jun 13 19:37:30 2017 From: ghc-devs at haskell.org (GHC) Date: Tue, 13 Jun 2017 19:37:30 -0000 Subject: [GHC] #13825: Allow multiple constructor fields occupy the same word Message-ID: <046.a33ec6522f3fa0ad8c7d0d60af2159aa@haskell.org> #13825: Allow multiple constructor fields occupy the same word -------------------------------------+------------------------------------- Reporter: michalt | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- The main goal is to reduce the overhead of things like: {{{#!hs data Bloated = Bloated {-# UNPACK #-} !Word8 {-# UNPACK #-} !Int8 {-# UNPACK #-} !Bool }}} Assuming 64-bit architecture, currently those fields will take 8 bytes each! So for this example we'd need: 8 bytes for header + 3 * 8 bytes for fields = 32 bytes. But we should be able to pack the fields into a single word (a word is 8 bytes and each field really only needs 1 byte) for a total of 16 bytes (8 bytes header + 8 bytes for fields, with the 5 bytes being "overhead" due to heap alignment). My understanding is that we need a few things to make this happen: - Ability to refer to fields that are packed into a single word (currently everything in GHC assumes that each field occupies a single word). Simon Marlow started working on this in https://phabricator.haskell.org/D38 - Introduce primitives like `Word8#`, `Int8#`, ... (currently `WordX` and `IntX` are defined as wrappers of `Word#` and `Int#` respectively) and change `WordX`/`IntX` definitions to use those primitives. - Figure out what to do with `Bool` (should it be just `Word8#`? should we have `Bool#`?) and change its definition (using pattern synonyms for `True`/`False`) Some additional info: - Thread on ghc-devs: https://mail.haskell.org/pipermail/ghc- devs/2017-June/014304.html -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jun 13 19:58:10 2017 From: ghc-devs at haskell.org (GHC) Date: Tue, 13 Jun 2017 19:58:10 -0000 Subject: [GHC] #13825: Allow multiple constructor fields occupy the same word In-Reply-To: <046.a33ec6522f3fa0ad8c7d0d60af2159aa@haskell.org> References: <046.a33ec6522f3fa0ad8c7d0d60af2159aa@haskell.org> Message-ID: <061.714460ecf1fc54a12a72335c390bab20@haskell.org> #13825: Allow multiple constructor fields occupy the same word -------------------------------------+------------------------------------- Reporter: michalt | Owner: michalt Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by michalt): * owner: (none) => michalt -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jun 13 22:27:22 2017 From: ghc-devs at haskell.org (GHC) Date: Tue, 13 Jun 2017 22:27:22 -0000 Subject: [GHC] #13825: Allow multiple constructor fields occupy the same word In-Reply-To: <046.a33ec6522f3fa0ad8c7d0d60af2159aa@haskell.org> References: <046.a33ec6522f3fa0ad8c7d0d60af2159aa@haskell.org> Message-ID: <061.c66d215c27861046db24c0263b0fb9a5@haskell.org> #13825: Allow multiple constructor fields occupy the same word -------------------------------------+------------------------------------- Reporter: michalt | Owner: michalt Type: bug | Status: new Priority: normal | Milestone: 8.4.1 Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #605 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by dfeuer): * related: => #605 * milestone: => 8.4.1 Comment: `Bool` isn't special, and shouldn't be. It's just an enumeration type, and should remain one. #605 suggests representing unboxed enumeration types as `Int#`. It seems that to get what you want, you'd want to do something like what `Binary` and `Cereal` do with sum types, using a different number of bits depending on the number of constructors. One big question is whether and how to support sub-byte-sized fields. It is possible, presumably at some performance cost, to pack a `Bool` (for instance) into a single bit. Is the cost enough to worry about? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jun 13 22:28:21 2017 From: ghc-devs at haskell.org (GHC) Date: Tue, 13 Jun 2017 22:28:21 -0000 Subject: [GHC] #13825: Allow multiple constructor fields occupy the same word In-Reply-To: <046.a33ec6522f3fa0ad8c7d0d60af2159aa@haskell.org> References: <046.a33ec6522f3fa0ad8c7d0d60af2159aa@haskell.org> Message-ID: <061.0cdc6a02262087031e6bf9435a685a2a@haskell.org> #13825: Allow multiple constructor fields occupy the same word -------------------------------------+------------------------------------- Reporter: michalt | Owner: michalt Type: bug | Status: new Priority: normal | Milestone: 8.4.1 Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #605 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by dfeuer): * cc: dfeuer (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jun 13 22:49:19 2017 From: ghc-devs at haskell.org (GHC) Date: Tue, 13 Jun 2017 22:49:19 -0000 Subject: [GHC] #13822: GHC not using injectivity? In-Reply-To: <051.2a3d251c10227c1a71de0d444bf548f8@haskell.org> References: <051.2a3d251c10227c1a71de0d444bf548f8@haskell.org> Message-ID: <066.444ec9209da677d040c84636ff5e0ec1@haskell.org> #13822: GHC not using injectivity? -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: fixed | Keywords: | InjectiveFamilies, TypeInType Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by Iceland_jack): * status: new => closed * resolution: => fixed Comment: Never mind, this works in 8.3 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jun 13 22:56:29 2017 From: ghc-devs at haskell.org (GHC) Date: Tue, 13 Jun 2017 22:56:29 -0000 Subject: [GHC] #13822: GHC not using injectivity? In-Reply-To: <051.2a3d251c10227c1a71de0d444bf548f8@haskell.org> References: <051.2a3d251c10227c1a71de0d444bf548f8@haskell.org> Message-ID: <066.b2ed9365036a00217ca3dbbe6872bf54@haskell.org> #13822: GHC not using injectivity? -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: fixed | Keywords: | InjectiveFamilies, TypeInType Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): Yes, I suspect that this is a slightly more involved version of #11348. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jun 13 22:59:00 2017 From: ghc-devs at haskell.org (GHC) Date: Tue, 13 Jun 2017 22:59:00 -0000 Subject: [GHC] #13822: GHC not using injectivity? In-Reply-To: <051.2a3d251c10227c1a71de0d444bf548f8@haskell.org> References: <051.2a3d251c10227c1a71de0d444bf548f8@haskell.org> Message-ID: <066.641dacf8d1a9fcbea63e1f904945a592@haskell.org> #13822: GHC not using injectivity? -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: fixed | Keywords: | InjectiveFamilies, TypeInType Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): Would someone like to add it as a regression test? It never does any harm! -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jun 14 01:46:30 2017 From: ghc-devs at haskell.org (GHC) Date: Wed, 14 Jun 2017 01:46:30 -0000 Subject: [GHC] #13782: Bullish use of Template Haskell's newName causes GHC internal error In-Reply-To: <050.355b0f2ffb6750de858fbc3a1ccc85be@haskell.org> References: <050.355b0f2ffb6750de858fbc3a1ccc85be@haskell.org> Message-ID: <065.a3d43e9282544eae1e0e2e3c9c387d91@haskell.org> #13782: Bullish use of Template Haskell's newName causes GHC internal error -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: carlostome Type: bug | Status: patch Priority: high | Milestone: 8.2.1 Component: Template Haskell | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: #12503 | Differential Rev(s): Phab:D3641 Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * status: new => patch * differential: => Phab:D3641 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jun 14 02:19:24 2017 From: ghc-devs at haskell.org (GHC) Date: Wed, 14 Jun 2017 02:19:24 -0000 Subject: [GHC] #13773: Types are not normalized in instance declarations In-Reply-To: <047.b99d4e95d0428b43aa3236e584c6e7ac@haskell.org> References: <047.b99d4e95d0428b43aa3236e584c6e7ac@haskell.org> Message-ID: <062.b9385798f902b08adeff04073f63b680@haskell.org> #13773: Types are not normalized in instance declarations -------------------------------------+------------------------------------- Reporter: augustss | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by goldfire): I agree with Simon's implementation plan in comment:6 -- not hard to do. But I'm still not sold that we want to have this feature. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jun 14 02:51:59 2017 From: ghc-devs at haskell.org (GHC) Date: Wed, 14 Jun 2017 02:51:59 -0000 Subject: [GHC] #13782: Bullish use of Template Haskell's newName causes GHC internal error In-Reply-To: <050.355b0f2ffb6750de858fbc3a1ccc85be@haskell.org> References: <050.355b0f2ffb6750de858fbc3a1ccc85be@haskell.org> Message-ID: <065.567a90326325cff0e0dab7a148dd6b85@haskell.org> #13782: Bullish use of Template Haskell's newName causes GHC internal error -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: carlostome Type: bug | Status: patch Priority: high | Milestone: 8.2.1 Component: Template Haskell | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: #12503 | Differential Rev(s): Phab:D3641 Wiki Page: | -------------------------------------+------------------------------------- Comment (by goldfire): I have [https://phabricator.haskell.org/D3641#103588 commented] on the Phab Diff. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jun 14 03:14:11 2017 From: ghc-devs at haskell.org (GHC) Date: Wed, 14 Jun 2017 03:14:11 -0000 Subject: [GHC] #9630: compile-time performance regression (probably due to Generics) In-Reply-To: <042.a529e5f70870528e7f8796a28ce82a84@haskell.org> References: <042.a529e5f70870528e7f8796a28ce82a84@haskell.org> Message-ID: <057.be3549c0df368e4156d7d49b1149b87c@haskell.org> #9630: compile-time performance regression (probably due to Generics) -------------------------------------+------------------------------------- Reporter: hvr | Owner: dfeuer Type: bug | Status: new Priority: high | Milestone: 8.2.1 Component: Compiler | Version: 7.9 Resolution: | Keywords: deriving- | perf, Generics Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: #9583, #10293, | Differential Rev(s): #13059, #10818 | Wiki Page: | -------------------------------------+------------------------------------- Comment (by dfeuer): Commit 2b74bd9d8b4c6b20f3e8d9ada12e7db645cc3c19 (Stop the specialiser generating loopy code) had a big positive impact here. My test case (as yet unpublished) compiles over twice as quickly. Edward's (when the specialization is cross-module) compiles something like one and a half times as quickly, and the unused method no longer hurts it (in fact it helps it slightly; perhaps the single-method class optimization burns a little time). So it looks pretty likely that this bug is squashed. I'll try to check a few more things before adding a test case and calling it done. I suspect it's still worth looking into the doubled constraint solving that came up in comment:55, but perhaps that should be a separate (lower priority) ticket. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jun 14 10:01:32 2017 From: ghc-devs at haskell.org (GHC) Date: Wed, 14 Jun 2017 10:01:32 -0000 Subject: [GHC] #13782: Bullish use of Template Haskell's newName causes GHC internal error In-Reply-To: <050.355b0f2ffb6750de858fbc3a1ccc85be@haskell.org> References: <050.355b0f2ffb6750de858fbc3a1ccc85be@haskell.org> Message-ID: <065.e495de79f23bb190d844c8c13032a2a5@haskell.org> #13782: Bullish use of Template Haskell's newName causes GHC internal error -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: carlostome Type: bug | Status: patch Priority: high | Milestone: 8.2.1 Component: Template Haskell | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: #12503 | Differential Rev(s): Phab:D3641 Wiki Page: | -------------------------------------+------------------------------------- Comment (by carlostome): The FreeKiTyVars datatype is local to the [https://git.haskell.org/ghc.git/blob/HEAD:/compiler/renamer/RnTypes.hs RnTypes] module, so I think the way to go is to change the [https://git.haskell.org/ghc.git/blob/HEAD:/compiler/basicTypes/OccName.hs#l446 OccSet] for a RdrSet (with the same API) and include this one on [https://git.haskell.org/ghc.git/blob/HEAD:/compiler/basicTypes/OccName.hs RdrName]. The only difficulty I find is to come up with a sensible Uniquable instance for RdrName. {{{ #!haskell instance Uniquable RdrName where getUnique (Exact name) = ... getUnique (Unqual occ) = ... getUnique (Qual mod occ) = ... getUnique (Orig mod occ) = ... }}} In the cases for '''Exact''' and '''Unqual''' we would like to tag the ''Unique'' of name and occ and for the cases of '''Qual''' and '''Orig''' to tag and combine somehow the Unques for mod and occ. How can we do this? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jun 14 10:24:43 2017 From: ghc-devs at haskell.org (GHC) Date: Wed, 14 Jun 2017 10:24:43 -0000 Subject: [GHC] #13825: Allow multiple constructor fields occupy the same word In-Reply-To: <046.a33ec6522f3fa0ad8c7d0d60af2159aa@haskell.org> References: <046.a33ec6522f3fa0ad8c7d0d60af2159aa@haskell.org> Message-ID: <061.2d47f29b5fdecb3c6acc165765ce9662@haskell.org> #13825: Allow multiple constructor fields occupy the same word -------------------------------------+------------------------------------- Reporter: michalt | Owner: michalt Type: bug | Status: new Priority: normal | Milestone: 8.4.1 Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #605 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by maoe): * cc: maoe (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jun 14 13:22:23 2017 From: ghc-devs at haskell.org (GHC) Date: Wed, 14 Jun 2017 13:22:23 -0000 Subject: [GHC] #13824: ghc 8.2 does not build for me on ppc64le In-Reply-To: <048.696afd9b4d70bfaf30354dc33faf7c20@haskell.org> References: <048.696afd9b4d70bfaf30354dc33faf7c20@haskell.org> Message-ID: <063.49dc3b812b643760729a412068ff6170@haskell.org> #13824: ghc 8.2 does not build for me on ppc64le ----------------------------------------+--------------------------------- Reporter: msuchanek | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.1-rc2 Resolution: | Keywords: Operating System: Linux | Architecture: powerpc64 Type of failure: Building GHC failed | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | ----------------------------------------+--------------------------------- Comment (by msuchanek): It is present in mk/build.mk.sample which is used in the build. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jun 14 15:21:46 2017 From: ghc-devs at haskell.org (GHC) Date: Wed, 14 Jun 2017 15:21:46 -0000 Subject: [GHC] #10833: Use injective type families (decomposition) when dealing with givens In-Reply-To: <048.a87fa063590f3f8feefba56badb8ff21@haskell.org> References: <048.a87fa063590f3f8feefba56badb8ff21@haskell.org> Message-ID: <063.8c8c2fb8fe7ef3387949fc4a19f30a57@haskell.org> #10833: Use injective type families (decomposition) when dealing with givens -------------------------------------+------------------------------------- Reporter: jstolarek | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 7.10.2 checker) | Keywords: TypeFamilies, Resolution: | InjectiveFamilies Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #6018, #11511, | Differential Rev(s): #12199 | Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * cc: RyanGlScott (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jun 14 15:26:33 2017 From: ghc-devs at haskell.org (GHC) Date: Wed, 14 Jun 2017 15:26:33 -0000 Subject: [GHC] #10833: Use injective type families (decomposition) when dealing with givens In-Reply-To: <048.a87fa063590f3f8feefba56badb8ff21@haskell.org> References: <048.a87fa063590f3f8feefba56badb8ff21@haskell.org> Message-ID: <063.b77367f9e1c62f30466d95a3d7d680b3@haskell.org> #10833: Use injective type families (decomposition) when dealing with givens -------------------------------------+------------------------------------- Reporter: jstolarek | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 7.10.2 checker) | Keywords: TypeFamilies, Resolution: | InjectiveFamilies Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #6018, #11511, | Differential Rev(s): #12199 | Wiki Page: | -------------------------------------+------------------------------------- Changes (by Iceland_jack): * cc: Iceland_jack (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jun 14 17:01:52 2017 From: ghc-devs at haskell.org (GHC) Date: Wed, 14 Jun 2017 17:01:52 -0000 Subject: [GHC] #13054: Generating unique names with template haskell In-Reply-To: <046.cab92fb9718af01c3a3ff4e0ae0e0c01@haskell.org> References: <046.cab92fb9718af01c3a3ff4e0ae0e0c01@haskell.org> Message-ID: <061.7fb915ff69718b8ad81a6e32e4d6574f@haskell.org> #13054: Generating unique names with template haskell -------------------------------------+------------------------------------- Reporter: tim-m89 | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): I recently ran into this with fixity declarations: {{{#!hs {-# LANGUAGE TemplateHaskell #-} module Bug where import Language.Haskell.TH $(do n1 <- newName "&&&" n2 <- newName "&&&" let mkDecs n = [ InfixD (Fixity 5 InfixL) n , SigD n (AppT (AppT ArrowT (ConT ''Bool)) (AppT (AppT ArrowT (ConT ''Bool)) (ConT ''Bool))) , FunD n [Clause [WildP,WildP] (NormalB (ConE 'False)) []] ] return (mkDecs n1 ++ mkDecs n2)) }}} {{{ $ /opt/ghc/8.2.1/bin/runghc -ddump-splices Bug.hs Bug.hs:(6,3)-(12,36): Splicing declarations do n1_a3Xj <- newName "&&&" n2_a3Xk <- newName "&&&" let mkDecs_a3Xl n_a3Xm = [InfixD (Fixity 5 InfixL) n_a3Xm, SigD n_a3Xm (AppT (AppT ArrowT (ConT ''Bool)) (AppT (AppT ArrowT (ConT ''Bool)) (ConT ''Bool))), FunD n_a3Xm [Clause [WildP, WildP] (NormalB (ConE 'False)) []]] return (mkDecs_a3Xl n1_a3Xj ++ mkDecs_a3Xl n2_a3Xk) ======> infixl 5 &&&_a4dl (&&&_a4dl) :: Bool -> Bool -> Bool (&&&_a4dl) _ _ = False infixl 5 &&&_a4dm (&&&_a4dm) :: Bool -> Bool -> Bool (&&&_a4dm) _ _ = False Bug.hs:6:3: error: Multiple fixity declarations for ‘&&&_a4dl’ also at Bug.hs:(6,3)-(12,36) | 6 | $(do n1 <- newName "&&&" | ^^^^^^^^^^^^^^^^^^^^^^... }}} (To be precise, you'd encounter the same issue if you commented out the line that gives you a fixity declaration, but that was the first place I noticed it.) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jun 14 17:59:48 2017 From: ghc-devs at haskell.org (GHC) Date: Wed, 14 Jun 2017 17:59:48 -0000 Subject: [GHC] #13708: Panic! (the "impossible" happened) bug in GHC 8.2.1 rc2 In-Reply-To: <044.2693b478252b11f06ab341e229ae44a3@haskell.org> References: <044.2693b478252b11f06ab341e229ae44a3@haskell.org> Message-ID: <059.01765a99707b51cab6dd007684c0dedd@haskell.org> #13708: Panic! (the "impossible" happened) bug in GHC 8.2.1 rc2 -------------------------------------+------------------------------------- Reporter: deech | Owner: (none) Type: bug | Status: merge Priority: normal | Milestone: 8.2.1 Component: Compiler | Version: 8.2.1-rc2 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | simplCore/should_compile/T13708 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): For the record, `T13708` fails on `ghc-8.2` even with comment:10 due to a call to `setIdDemandInfo` in `DmdAnal.hs`, around line 300. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jun 14 18:11:36 2017 From: ghc-devs at haskell.org (GHC) Date: Wed, 14 Jun 2017 18:11:36 -0000 Subject: =?utf-8?b?UmU6IFtHSENdICMxMzYxNTogTm9uZGV0ZXJtaW5pc20gaW4g4oCY?= =?utf-8?q?pure=E2=80=99_function_w/_parallel_evaluation_=26_memo?= =?utf-8?q?_combinators?= In-Reply-To: <044.57733831351687fff6258688df1f42f7@haskell.org> References: <044.57733831351687fff6258688df1f42f7@haskell.org> Message-ID: <059.32436ecb271e1d482e3280ec7a4e5168@haskell.org> #13615: Nondeterminism in ‘pure’ function w/ parallel evaluation & memo combinators -------------------------------------+------------------------------------- Reporter: pacak | Owner: bgamari Type: bug | Status: new Priority: highest | Milestone: 8.2.1 Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): simonmar, does comment:36 sound at all plausible? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jun 14 18:27:03 2017 From: ghc-devs at haskell.org (GHC) Date: Wed, 14 Jun 2017 18:27:03 -0000 Subject: =?utf-8?b?UmU6IFtHSENdICMxMzYxNTogTm9uZGV0ZXJtaW5pc20gaW4g4oCY?= =?utf-8?q?pure=E2=80=99_function_w/_parallel_evaluation_=26_memo?= =?utf-8?q?_combinators?= In-Reply-To: <044.57733831351687fff6258688df1f42f7@haskell.org> References: <044.57733831351687fff6258688df1f42f7@haskell.org> Message-ID: <059.1564ac009f0a68c7015f3824547a6bfa@haskell.org> #13615: Nondeterminism in ‘pure’ function w/ parallel evaluation & memo combinators -------------------------------------+------------------------------------- Reporter: pacak | Owner: bgamari Type: bug | Status: new Priority: highest | Milestone: 8.2.1 Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): I should also mention that the variant prepared by dfeuer in comment:37 also exhibits this bug. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jun 14 18:51:29 2017 From: ghc-devs at haskell.org (GHC) Date: Wed, 14 Jun 2017 18:51:29 -0000 Subject: [GHC] #13799: -ddump-splices prints out declarations in the wrong order In-Reply-To: <050.f45d5f324cc6583163c58bb2b6f6629d@haskell.org> References: <050.f45d5f324cc6583163c58bb2b6f6629d@haskell.org> Message-ID: <065.ba4599effc471de8d5653b70201e15f9@haskell.org> #13799: -ddump-splices prints out declarations in the wrong order -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Debugging | Unknown/Multiple information is incorrect | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): More generally, GHC seems to be pretty cavalier in modifying the quasiquoted declarations before pretty-printing them. Here's another example: {{{#!hs {-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE TypeOperators #-} {-# OPTIONS_GHC -ddump-splices #-} module Bug where $([d| infixr 5 :*: data a :*: b = a :*: b |]) }}} {{{ $ /opt/ghc/8.2.1/bin/runghc Bug.hs Bug.hs:(6,3)-(8,6): Splicing declarations [d| infixr 5 :*:_a1pB, :*:_a1pA data a_a1pC :*:_a1pA b_a1pD = a_a1pC :*:_a1pB b_a1pD |] ======> infixr 5 :*:_a4aj infixr 5 :*:_a4ai data (:*:_a4ai) a_a4ak b_a4al = a_a4ak :*:_a4aj b_a4al Bug.hs:6:3: error: Multiple fixity declarations for ‘:*:_a4aj’ also at Bug.hs:(6,3)-(8,6) | 6 | $([d| infixr 5 :*: | ^^^^^^^^^^^^^^^^... }}} Because `(:*:)` is used in both the type and value namespace, GHC seems to be creating //two// `newName`s for `:*:` behind the hood, and changing the data/fixity declarations accordingly. (Notice that the fixity declaration has two identifiers now!) It then proceeds to fail to compile due to #13054, but that's a separate issue. The issue at hand is that `-ddump- splices` is printing out internal details in the quasiquoted `[d| ... |]` declarations, when it really needn't. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jun 14 19:46:39 2017 From: ghc-devs at haskell.org (GHC) Date: Wed, 14 Jun 2017 19:46:39 -0000 Subject: [GHC] #13739: Very slow linking of profiled executables In-Reply-To: <043.2d2650cd128632597774b5afb6c7a225@haskell.org> References: <043.2d2650cd128632597774b5afb6c7a225@haskell.org> Message-ID: <058.111382b03922473dc97af4aada28790c@haskell.org> #13739: Very slow linking of profiled executables -------------------------------------+------------------------------------- Reporter: duog | Owner: (none) Type: bug | Status: new Priority: high | Milestone: 8.2.1 Component: Compiler | Version: 8.2.1-rc2 Resolution: | Keywords: Operating System: Linux | Architecture: x86_64 Type of failure: Compile-time | (amd64) performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by duog): Another note: -split-sections does not apply to shared libraries, and passing -dynamic to ghc shows no difference between 8.0.2 and 8.2.1. Profiled dynamic libraries do not appear to be packaged, so I have not tested the -dynamic -prof case, but I'd expect there to be no difference there either. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jun 14 20:10:36 2017 From: ghc-devs at haskell.org (GHC) Date: Wed, 14 Jun 2017 20:10:36 -0000 Subject: [GHC] #13826: :t Predicate (length :: [] -> Int) Message-ID: <044.921aed78ef13cc5e22c3dc592b9a1198@haskell.org> #13826: :t Predicate (length :: [] -> Int) --------------------------------+------------------------------------- Reporter: dpsrt | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.2 Keywords: | Operating System: Unknown/Multiple Architecture: Other | Type of failure: None/Unknown Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: --------------------------------+------------------------------------- {{{ Prelude> :t Predicate (length :: [] -> Int) ghc: panic! (the 'impossible' happened) (GHC version 8.0.2 for x86_64-unknown-mingw32): initTc: unsolved constraints WC {wc_insol = [W] Predicate_a64B :: t_a64A[tau:3] (CHoleCan: Predicate)} }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jun 14 20:20:33 2017 From: ghc-devs at haskell.org (GHC) Date: Wed, 14 Jun 2017 20:20:33 -0000 Subject: [GHC] #13827: "What AbsBinds means" is a pretty confusing doc comment Message-ID: <046.d6811ad66cde747388ca38ca27c2378f@haskell.org> #13827: "What AbsBinds means" is a pretty confusing doc comment -------------------------------------+------------------------------------- Reporter: literon | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Documentation | Version: 8.0.1 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- See the note in https://downloads.haskell.org/~ghc/8.0.1/docs/html/libraries/ghc-8.0.1/src/HsBinds.html named "What AbsBinds means". It seems like the example refers variables that are not defined (at least in the example), for example `gp`. Also, a bit more verbose text would be welcome (aka I have no idea what is going on). Thank you! -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jun 14 21:19:34 2017 From: ghc-devs at haskell.org (GHC) Date: Wed, 14 Jun 2017 21:19:34 -0000 Subject: [GHC] #13826: :t Predicate (length :: [] -> Int) In-Reply-To: <044.921aed78ef13cc5e22c3dc592b9a1198@haskell.org> References: <044.921aed78ef13cc5e22c3dc592b9a1198@haskell.org> Message-ID: <059.75467becf028eb14616b8b7728085315@haskell.org> #13826: :t Predicate (length :: [] -> Int) -------------------------------------+------------------------------ Reporter: dpsrt | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 8.0.2 Resolution: duplicate | Keywords: Operating System: Unknown/Multiple | Architecture: Other Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #13106 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------ Changes (by RyanGlScott): * status: new => closed * resolution: => duplicate * related: => #13106 Comment: Thanks for the bug report. This is a duplicate of #13106, which has been fixed in GHC 8.2. Note that this panic is usually caused by using identifiers that aren't in-scope (in your case, `Predicate`) in just the right way. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jun 14 22:03:47 2017 From: ghc-devs at haskell.org (GHC) Date: Wed, 14 Jun 2017 22:03:47 -0000 Subject: [GHC] #13782: Bullish use of Template Haskell's newName causes GHC internal error In-Reply-To: <050.355b0f2ffb6750de858fbc3a1ccc85be@haskell.org> References: <050.355b0f2ffb6750de858fbc3a1ccc85be@haskell.org> Message-ID: <065.301477ada9c044cd22678127ccafdda9@haskell.org> #13782: Bullish use of Template Haskell's newName causes GHC internal error -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: carlostome Type: bug | Status: patch Priority: high | Milestone: 8.2.1 Component: Template Haskell | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: #12503 | Differential Rev(s): Phab:D3641 Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): I agree with Richard's comment that the fix is suspicous. For now, let's just dump the `OccSets` entirely, and filter the `RdrName` lists. This will actually be more efficient in the common case of small sets. If we find programs with zillions of foralls we can deal with it then. Incidentally, even as it stands we call `nub` on these lists, and there is lots of appending, which is equally quadratic. I believe, but I am not sure, that `fkfv_all = fktv_kis ++ kktv_tys`. Assuming so, let's dump `fktv_all` too leaving only two fields, and just append when needed. Unless the ''order'' is significant? Nothing in the comments suggest that it is. Richard? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jun 15 00:20:59 2017 From: ghc-devs at haskell.org (GHC) Date: Thu, 15 Jun 2017 00:20:59 -0000 Subject: [GHC] #13828: Re-linking is not avoided when -dynamic is used Message-ID: <042.c773e7cc977220155c35e7ac14fb0060@haskell.org> #13828: Re-linking is not avoided when -dynamic is used -------------------------------------+------------------------------------- Reporter: nh2 | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.2 (Linking) | Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- In normal builds, GHC will no re-link executables when that's not necesary (e.g. when no code has changed). But when `-dynamic` is used, it re-links every time. Minimal example for reproduction: https://github.com/nh2/cabal-relink-test -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jun 15 00:46:05 2017 From: ghc-devs at haskell.org (GHC) Date: Thu, 15 Jun 2017 00:46:05 -0000 Subject: [GHC] #13828: Re-linking is not avoided when -dynamic is used In-Reply-To: <042.c773e7cc977220155c35e7ac14fb0060@haskell.org> References: <042.c773e7cc977220155c35e7ac14fb0060@haskell.org> Message-ID: <057.2f0e4434f7630c7729a5677eb20a6db3@haskell.org> #13828: Re-linking is not avoided when -dynamic is used -------------------------------------+------------------------------------- Reporter: nh2 | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.2 (Linking) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by nh2): When using `cabal build -v`, we see these ghc invocations: {{{ Component build order: library, executable 'cabal-relink-test' creating dist/build creating dist/build/autogen Building cabal-relink-test-0.1.0.0... /path/to/ghc-8.0.2-with-packages/bin/ghc-pkg init dist/package.conf.inplace Preprocessing library cabal-relink-test-0.1.0.0... Building library... creating dist/build /path/to/ghc-8.0.2-with-packages/bin/ghc --make -fbuilding-cabal-package -O -j4 -static -dynamic-too -dynosuf dyn_o -dynhisuf dyn_hi -outputdir dist/build -odir dist/build -hidir dist/build -stubdir dist/build -i -idist/build -isrc -idist/build/autogen -Idist/build/autogen -Idist/build -optP-include -optPdist/build/autogen/cabal_macros.h -this-unit-id cabal- relink-test-0.1.0.0-9KTeoqstB5uArQE6VcRCGn -hide-all-packages -package-db dist/package.conf.inplace -package-id base-4.9.1.0 -XHaskell2010 Mymodule Linking... [(SimpleUnitId (ComponentId "base-4.9.1.0"),PackageIdentifier {pkgName = PackageName {unPackageName = "base"}, pkgVersion = Version {versionBranch = [4,9,1,0], versionTags = []}},ModuleRenaming True [])] /path/to/binutils-2.27/bin/ar -r dist/build/objs-18165/libHScabal-relink- test-0.1.0.0-9KTeoqstB5uArQE6VcRCGn.a dist/build/Mymodule.o /path/to/binutils-2.27/bin/ar: creating dist/build/objs-18165/libHScabal- relink-test-0.1.0.0-9KTeoqstB5uArQE6VcRCGn.a /path/to/ghc-8.0.2-with-packages/bin/ghc -shared -dynamic '-dynload deploy' -optl-Wl,-rpath,/path/to/ghc-8.0.2/lib/ghc-8.0.2/base-4.9.1.0 -optl-Wl,-rpath,/path/to/ghc-8.0.2/lib/ghc-8.0.2/ghc-prim-0.5.0.0 -optl- Wl,-rpath,/path/to/ghc-8.0.2/lib/ghc-8.0.2/integer-gmp-1.0.0.1 -optl- Wl,-rpath,/path/to/gmp-6.1.1/lib -optl- Wl,-rpath,/path/to/ghc-8.0.2/lib/ghc-8.0.2/rts -hide-all-packages -no- auto-link-packages -package-db dist/package.conf.inplace -package-id base-4.9.1.0 dist/build/Mymodule.dyn_o -o dist/build/libHScabal-relink- test-0.1.0.0-9KTeoqstB5uArQE6VcRCGn-ghc8.0.2.so /path/to/ghc-8.0.2-with-packages/bin/ghc-pkg update - --global --user '--package-db=dist/package.conf.inplace' Preprocessing executable 'cabal-relink-test' for cabal-relink- test-0.1.0.0... Building executable cabal-relink-test... creating dist/build/cabal-relink-test creating dist/build/cabal-relink-test/cabal-relink-test-tmp /path/to/ghc-8.0.2-with-packages/bin/ghc --make -no-link -fbuilding-cabal- package -O -j4 -static -outputdir dist/build/cabal-relink-test/cabal- relink-test-tmp -odir dist/build/cabal-relink-test/cabal-relink-test-tmp -hidir dist/build/cabal-relink-test/cabal-relink-test-tmp -stubdir dist/build/cabal-relink-test/cabal-relink-test-tmp -i -idist/build/cabal- relink-test/cabal-relink-test-tmp -iapp -idist/build/autogen -Idist/build/autogen -Idist/build/cabal-relink-test/cabal-relink-test-tmp -optP-include -optPdist/build/autogen/cabal_macros.h -hide-all-packages -package-db dist/package.conf.inplace -package-id base-4.9.1.0 -package-id cabal-relink-test-0.1.0.0-9KTeoqstB5uArQE6VcRCGn -XHaskell2010 app/Main.hs -dynamic Linking... /path/to/ghc-8.0.2-with-packages/bin/ghc --make -fbuilding-cabal-package -O -static -outputdir dist/build/cabal-relink-test/cabal-relink-test-tmp -odir dist/build/cabal-relink-test/cabal-relink-test-tmp -hidir dist/build /cabal-relink-test/cabal-relink-test-tmp -stubdir dist/build/cabal-relink- test/cabal-relink-test-tmp -i -idist/build/cabal-relink-test/cabal-relink- test-tmp -iapp -idist/build/autogen -Idist/build/autogen -Idist/build /cabal-relink-test/cabal-relink-test-tmp -optP-include -optPdist/build/autogen/cabal_macros.h -hide-all-packages -package-db dist/package.conf.inplace -package-id base-4.9.1.0 -package-id cabal- relink-test-0.1.0.0-9KTeoqstB5uArQE6VcRCGn -XHaskell2010 app/Main.hs -o dist/build/cabal-relink-test/cabal-relink-test -dynamic Linking dist/build/cabal-relink-test/cabal-relink-test ... }}} The following 2 GHC invocations are of interest: 1. Building the shared library `.so` file for the cabal `library`: `ghc -shared -dynamic '-dynload deploy' -optl- Wl,-rpath,/path/to/lib/ghc-8.0.2/base-4.9.1.0 -optl- Wl,-rpath,/path/to/lib/ghc-8.0.2/ghc-prim-0.5.0.0 -optl- Wl,-rpath,/path/to/lib/ghc-8.0.2/integer-gmp-1.0.0.1 -optl- Wl,-rpath,/path/to/gmp-6.1.1/lib -optl- Wl,-rpath,/path/to/lib/ghc-8.0.2/rts -hide-all-packages -no-auto-link- packages -package-db dist/package.conf.inplace -package-id base-4.9.1.0 dist/build/Mymodule.dyn_o -o dist/build/libHScabal-relink-test-0.1.0.0 -9KTeoqstB5uArQE6VcRCGn-ghc8.0.2.so` 2. Building the dynamically linked executable: `ghc --make -fbuilding-cabal-package -O -static -outputdir dist/build /cabal-relink-test/cabal-relink-test-tmp -odir dist/build/cabal-relink- test/cabal-relink-test-tmp -hidir dist/build/cabal-relink-test/cabal- relink-test-tmp -stubdir dist/build/cabal-relink-test/cabal-relink-test- tmp -i -idist/build/cabal-relink-test/cabal-relink-test-tmp -iapp -idist/build/autogen -Idist/build/autogen -Idist/build/cabal-relink-test /cabal-relink-test-tmp -optP-include -optPdist/build/autogen/cabal_macros.h -hide-all-packages -package-db dist/package.conf.inplace -package-id base-4.9.1.0 -package-id cabal- relink-test-0.1.0.0-9KTeoqstB5uArQE6VcRCGn -XHaskell2010 app/Main.hs -o dist/build/cabal-relink-test/cabal-relink-test -rtsopts -dynamic` The first invocation always touches (updates the mtime of) `dist/build/libHScabal-relink-test-0.1.0.0-9KTeoqstB5uArQE6VcRCGn- ghc8.0.2.so` and when the second one sees the mtime updated, it relinks. From a quick look at the code, I think the reason is this: In `linkingNeeded` in https://github.com/ghc/ghc/blob/ghc-8.0.2-release/compiler/main/DriverPipeline.hs#L420-L427 {{{ let pkg_hslibs = [ (collectLibraryPaths dflags [c], lib) | Just c <- map (lookupPackage dflags) pkg_deps, lib <- packageHsLibs dflags c ] pkg_libfiles <- mapM (uncurry (findHSLib dflags)) pkg_hslibs if any isNothing pkg_libfiles then return True else do e_lib_times <- mapM (tryIO . getModificationUTCTime) (catMaybes pkg_libfiles) }}} I suspect that when linking statically, `pkg_libfiles` is empty, and when linking dynamically, it contains the above mentioned `.so` file; then, if the `.so` file was touched `linkingNeeded` returns `True`, and it relinks. Now the question is: Why does the mtime of the `.so` file change at all? It's simply because ghc unconditionally invokes `ld` (through `gcc`, or more precisely, whatever is configured as the linker program `pgm_l`) here in `linkDynLib`: https://github.com/ghc/ghc/blob/ghc-8.0.2-release/compiler/main/SysTools.hs#L1720-L1724 {{{ runLink dflags ( map Option verbFlags ++ [ Option "-o" , FileOption "" output_fn , Option "-shared" ] ++ ... ... }}} And `ld` will always touch the `-o` output file. What's not clear to me is where the chain should have ended: * Should `linkDynLib` have not been called in the first place? * Or should `linkDynLib` only touch the file when the contents change (e.g. by writing it somewhere else, and doing a `mv` after a contents comparison; cabal does that in a couple places)? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jun 15 00:53:08 2017 From: ghc-devs at haskell.org (GHC) Date: Thu, 15 Jun 2017 00:53:08 -0000 Subject: [GHC] #13828: Re-linking is not avoided when -dynamic is used In-Reply-To: <042.c773e7cc977220155c35e7ac14fb0060@haskell.org> References: <042.c773e7cc977220155c35e7ac14fb0060@haskell.org> Message-ID: <057.a4198f55fc4a21de20f0c3bfd7534e5c@haskell.org> #13828: Re-linking is not avoided when -dynamic is used -------------------------------------+------------------------------------- Reporter: nh2 | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.2 (Linking) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by nh2): Note that this issue is not present when linking directly with `ghc --make`: {{{ $ ghc --make -isrc app/Main.hs [1 of 2] Compiling Mymodule ( src/Mymodule.hs, src/Mymodule.o ) [2 of 2] Compiling Main ( app/Main.hs, app/Main.o ) Linking app/Main ... $ ghc --make -isrc app/Main.hs $ }}} {{{ $ ghc --make -isrc app/Main.hs -dynamic [1 of 2] Compiling Mymodule ( src/Mymodule.hs, src/Mymodule.o ) [2 of 2] Compiling Main ( app/Main.hs, app/Main.o ) Linking app/Main ... $ ghc --make -isrc app/Main.hs -dynamic $ }}} Avoids relinking just fine. So I wonder what triggers it in the above case with cabal. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jun 15 01:11:05 2017 From: ghc-devs at haskell.org (GHC) Date: Thu, 15 Jun 2017 01:11:05 -0000 Subject: [GHC] #13829: ghc --make should not relink when we know the binary doesn't change Message-ID: <042.29f72bff1cb1d2cf0374d6e7c8a4ed62@haskell.org> #13829: ghc --make should not relink when we know the binary doesn't change -------------------------------------+------------------------------------- Reporter: nh2 | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.2 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: #13828 Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- I would expect GHC not to relink after touching a file, since no actual program code was changed. But it does: {{{ $ echo "main = return ()" > Main.hs $ ghc --make Main.hs [1 of 1] Compiling Main ( Main.hs, Main.o ) Linking Main ... $ touch Main.hs $ ghc --make Main.hs [1 of 1] Compiling Main ( Main.hs, Main.o ) Linking Main ... }}} I would expect that the recompilation avoidance makes GHC stop continuing as soon as it has noticed that the same object code (`.o` file) was generated as in the first build. Perhaps even earlier (e.g. after parsing). -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jun 15 01:13:43 2017 From: ghc-devs at haskell.org (GHC) Date: Thu, 15 Jun 2017 01:13:43 -0000 Subject: [GHC] #13829: ghc --make should not relink when we know the binary doesn't change In-Reply-To: <042.29f72bff1cb1d2cf0374d6e7c8a4ed62@haskell.org> References: <042.29f72bff1cb1d2cf0374d6e7c8a4ed62@haskell.org> Message-ID: <057.adae86cc28e7d001aa8e8b26fe96cb1d@haskell.org> #13829: ghc --make should not relink when we know the binary doesn't change -------------------------------------+------------------------------------- Reporter: nh2 | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #13828 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Description changed by nh2: @@ -22,1 +22,6 @@ - Perhaps even earlier (e.g. after parsing). + Perhaps even earlier (e.g. after parsing) in this specific case; but + certainly after code gen, which I'd expect also to avoid the recompilation + if e.g. a comment was added to the file, as the comment won't make it into + the program code (unless something like TH `location` or `HasCallStack` is + used, which can change the line numbers those generate if a comment pushes + them down). New description: I would expect GHC not to relink after touching a file, since no actual program code was changed. But it does: {{{ $ echo "main = return ()" > Main.hs $ ghc --make Main.hs [1 of 1] Compiling Main ( Main.hs, Main.o ) Linking Main ... $ touch Main.hs $ ghc --make Main.hs [1 of 1] Compiling Main ( Main.hs, Main.o ) Linking Main ... }}} I would expect that the recompilation avoidance makes GHC stop continuing as soon as it has noticed that the same object code (`.o` file) was generated as in the first build. Perhaps even earlier (e.g. after parsing) in this specific case; but certainly after code gen, which I'd expect also to avoid the recompilation if e.g. a comment was added to the file, as the comment won't make it into the program code (unless something like TH `location` or `HasCallStack` is used, which can change the line numbers those generate if a comment pushes them down). -- -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jun 15 01:22:34 2017 From: ghc-devs at haskell.org (GHC) Date: Thu, 15 Jun 2017 01:22:34 -0000 Subject: [GHC] #13009: Hierarchical Module Structure for GHC In-Reply-To: <045.859215149771e4346ac45f933feca22e@haskell.org> References: <045.859215149771e4346ac45f933feca22e@haskell.org> Message-ID: <060.40d233b246890c56c723f3b04b8a2a35@haskell.org> #13009: Hierarchical Module Structure for GHC -------------------------------------+------------------------------------- Reporter: hsyl20 | Owner: hsyl20 Type: task | Status: patch Priority: low | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3647 Wiki Page: | ModuleDependencies/Hierarchical | -------------------------------------+------------------------------------- Changes (by hsyl20): * status: new => patch * differential: => Phab:D3647 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jun 15 02:28:22 2017 From: ghc-devs at haskell.org (GHC) Date: Thu, 15 Jun 2017 02:28:22 -0000 Subject: [GHC] #13782: Bullish use of Template Haskell's newName causes GHC internal error In-Reply-To: <050.355b0f2ffb6750de858fbc3a1ccc85be@haskell.org> References: <050.355b0f2ffb6750de858fbc3a1ccc85be@haskell.org> Message-ID: <065.41c0e1f5ea52a171d35b470d4d05fdad@haskell.org> #13782: Bullish use of Template Haskell's newName causes GHC internal error -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: carlostome Type: bug | Status: patch Priority: high | Milestone: 8.2.1 Component: Template Haskell | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: #12503 | Differential Rev(s): Phab:D3641 Wiki Page: | -------------------------------------+------------------------------------- Comment (by goldfire): A variable could conceivably be mentioned in both `ftkv_kis` and `ftkv_tys`, so naive appending might cause duplication. I don't think order is significant. If it turns out to be somewhere, we could always use the source locations to restore order. Agreed with Simon's plan in comment:10. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jun 15 03:04:48 2017 From: ghc-devs at haskell.org (GHC) Date: Thu, 15 Jun 2017 03:04:48 -0000 Subject: [GHC] #13756: Typo in user guide suggests that there's an -O* option In-Reply-To: <042.6a3b1c429314348df414591c312b566f@haskell.org> References: <042.6a3b1c429314348df414591c312b566f@haskell.org> Message-ID: <057.18c0b560413d73c6e68af6f9b446a407@haskell.org> #13756: Typo in user guide suggests that there's an -O* option -------------------------------------+------------------------------------- Reporter: nh2 | Owner: SantiM Type: bug | Status: closed Priority: normal | Milestone: 8.2.1 Component: Documentation | Version: 8.0.2 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3631 Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): Merged to `ghc-8.2` in 5eb4a35bcc6743fce33eaf42b15d17e48936e41f. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jun 15 03:05:40 2017 From: ghc-devs at haskell.org (GHC) Date: Thu, 15 Jun 2017 03:05:40 -0000 Subject: [GHC] #13429: Optimizer produces Core with an infinite <> In-Reply-To: <045.cf5ba15167896826f7f0c0a59d69b609@haskell.org> References: <045.cf5ba15167896826f7f0c0a59d69b609@haskell.org> Message-ID: <060.a56eb45e881fa4412725c9bf5494dd00@haskell.org> #13429: Optimizer produces Core with an infinite <> -------------------------------------+------------------------------------- Reporter: lehins | Owner: simonpj Type: bug | Status: closed Priority: highest | Milestone: 8.2.1 Component: Compiler | Version: 8.0.2 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Runtime crash | Test Case: | simplCore/should_run/T13429, | T13429_2 Blocked By: | Blocking: Related Tickets: #13750, #12545 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: merge => closed * resolution: => fixed Comment: Merged to `ghc-8.2` in a7a1d7fdcd3e34787f28be4eb24645c2e14a9f3d. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jun 15 03:38:26 2017 From: ghc-devs at haskell.org (GHC) Date: Thu, 15 Jun 2017 03:38:26 -0000 Subject: [GHC] #13830: '+RTS -s' gives incorrect value for work balance in some cases Message-ID: <043.14e010bc8c8133d891369e32e6e80a21@haskell.org> #13830: '+RTS -s' gives incorrect value for work balance in some cases -------------------------------------+------------------------------------- Reporter: duog | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Runtime | Version: 8.0.1 System | Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: Debugging Unknown/Multiple | information is incorrect Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- The formula for work balance as printed by the rts -s flag does not account for the possibility of the number of capabilities changing. Nor does it account for the number of garbage collection threads being other than n_capabilities. The attached program demonstrates the first problem, with instructions for replication in comments. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jun 15 03:38:42 2017 From: ghc-devs at haskell.org (GHC) Date: Thu, 15 Jun 2017 03:38:42 -0000 Subject: [GHC] #13830: '+RTS -s' gives incorrect value for work balance in some cases In-Reply-To: <043.14e010bc8c8133d891369e32e6e80a21@haskell.org> References: <043.14e010bc8c8133d891369e32e6e80a21@haskell.org> Message-ID: <058.c3e05437dcbe149c41f6cdcbcd98ec4e@haskell.org> #13830: '+RTS -s' gives incorrect value for work balance in some cases -------------------------------------+------------------------------------- Reporter: duog | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Runtime System | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Debugging | Unknown/Multiple information is incorrect | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by duog): * Attachment "Main.hs" added. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jun 15 04:29:39 2017 From: ghc-devs at haskell.org (GHC) Date: Thu, 15 Jun 2017 04:29:39 -0000 Subject: [GHC] #13831: GHCi ignores -fforce-recomp on first :reload when used with custom preprocessor Message-ID: <050.56928813447af0d3a11b2eab946dcdf2@haskell.org> #13831: GHCi ignores -fforce-recomp on first :reload when used with custom preprocessor -------------------------------------+------------------------------------- Reporter: SimonHengel | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: GHCi | Version: 8.0.2 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- Steps to reproduce: {{{#!bash #!/bin/bash # file preprocess.sh echo "main = putStrLn \"`date -u`\"" > "$3" echo "Reloaded!" }}} {{{#!hs -- file Main.hs {-# OPTIONS_GHC -fforce-recomp -F -pgmF preprocess.sh #-} }}} {{{ $ chmod +x preprocess.sh $ PATH=.:$PATH ghci Main.hs -v0 Reloaded! *Main> main Thu Jun 15 04:15:26 UTC 2017 *Main> :reload *Main> main Thu Jun 15 04:15:26 UTC 2017 *Main> :reload Reloaded! *Main> main Thu Jun 15 04:15:35 UTC 2017 }}} As is evident from the output above, the first `:reload` got lost; {{{preprocessor.sh}}} is not executed at all. The second `:reload` works as expected. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jun 15 04:31:18 2017 From: ghc-devs at haskell.org (GHC) Date: Thu, 15 Jun 2017 04:31:18 -0000 Subject: [GHC] #13831: GHCi ignores -fforce-recomp on first :reload when used with custom preprocessor In-Reply-To: <050.56928813447af0d3a11b2eab946dcdf2@haskell.org> References: <050.56928813447af0d3a11b2eab946dcdf2@haskell.org> Message-ID: <065.3391108c083e6551de086b496297c362@haskell.org> #13831: GHCi ignores -fforce-recomp on first :reload when used with custom preprocessor -------------------------------------+------------------------------------- Reporter: SimonHengel | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: GHCi | Version: 8.0.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Description changed by SimonHengel: @@ -21,0 +21,2 @@ + }}} + {{{ @@ -24,0 +26,2 @@ + }}} + {{{ New description: Steps to reproduce: {{{#!bash #!/bin/bash # file preprocess.sh echo "main = putStrLn \"`date -u`\"" > "$3" echo "Reloaded!" }}} {{{#!hs -- file Main.hs {-# OPTIONS_GHC -fforce-recomp -F -pgmF preprocess.sh #-} }}} {{{ $ chmod +x preprocess.sh $ PATH=.:$PATH ghci Main.hs -v0 Reloaded! *Main> main Thu Jun 15 04:15:26 UTC 2017 }}} {{{ *Main> :reload *Main> main Thu Jun 15 04:15:26 UTC 2017 }}} {{{ *Main> :reload Reloaded! *Main> main Thu Jun 15 04:15:35 UTC 2017 }}} As is evident from the output above, the first `:reload` got lost; {{{preprocessor.sh}}} is not executed at all. The second `:reload` works as expected. -- -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jun 15 04:34:39 2017 From: ghc-devs at haskell.org (GHC) Date: Thu, 15 Jun 2017 04:34:39 -0000 Subject: [GHC] #13831: GHCi ignores -fforce-recomp on first :reload when used with custom preprocessor In-Reply-To: <050.56928813447af0d3a11b2eab946dcdf2@haskell.org> References: <050.56928813447af0d3a11b2eab946dcdf2@haskell.org> Message-ID: <065.fe94733a2c5235fdb46add848074b60e@haskell.org> #13831: GHCi ignores -fforce-recomp on first :reload when used with custom preprocessor -------------------------------------+------------------------------------- Reporter: SimonHengel | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: GHCi | Version: 8.0.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by SimonHengel): Possibly related to #6105 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jun 15 08:51:11 2017 From: ghc-devs at haskell.org (GHC) Date: Thu, 15 Jun 2017 08:51:11 -0000 Subject: [GHC] #13009: Hierarchical Module Structure for GHC In-Reply-To: <045.859215149771e4346ac45f933feca22e@haskell.org> References: <045.859215149771e4346ac45f933feca22e@haskell.org> Message-ID: <060.ec9a3761763c55f67dd79fc39567f150@haskell.org> #13009: Hierarchical Module Structure for GHC -------------------------------------+------------------------------------- Reporter: hsyl20 | Owner: hsyl20 Type: task | Status: patch Priority: low | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3647 Wiki Page: | ModuleDependencies/Hierarchical | -------------------------------------+------------------------------------- Comment (by hvr): Do we have numbers on how many packages actually directly depend on `ghc` (i.e. reverse deps) and thus actually suffer from the namespace clash? There's also the option to have a pure reexporting package which uses Cabal's feature to reexport modules at the cabal level under a different name: ModuleReexports; that way we could experiment with a new hierarchy without having to commit to it just yet. And once we're convinced we could do a physical reshuffling. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jun 15 11:37:24 2017 From: ghc-devs at haskell.org (GHC) Date: Thu, 15 Jun 2017 11:37:24 -0000 Subject: =?utf-8?b?UmU6IFtHSENdICMxMzYxNTogTm9uZGV0ZXJtaW5pc20gaW4g4oCY?= =?utf-8?q?pure=E2=80=99_function_w/_parallel_evaluation_=26_memo?= =?utf-8?q?_combinators?= In-Reply-To: <044.57733831351687fff6258688df1f42f7@haskell.org> References: <044.57733831351687fff6258688df1f42f7@haskell.org> Message-ID: <059.2326f4aef5ef173dc9271999479e8d59@haskell.org> #13615: Nondeterminism in ‘pure’ function w/ parallel evaluation & memo combinators -------------------------------------+------------------------------------- Reporter: pacak | Owner: bgamari Type: bug | Status: new Priority: highest | Milestone: 8.2.1 Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by andrewthad): I have simplified the example failure here: https://github.com/andrewthad /cuddly-bassoon/tree/9e87acbc43b10d38758e6263b8d17231cb1f3ed7 In this commit, I entirely removed the use of hashmap and hashable. I'm just adding up the numbers in an STRef, and the problem still shows up. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jun 15 13:49:52 2017 From: ghc-devs at haskell.org (GHC) Date: Thu, 15 Jun 2017 13:49:52 -0000 Subject: [GHC] #13832: No parameter-validation in Control.Concurrent.setNumCapabilities Message-ID: <051.3d60dff1f88e30b72e07c48763136ae0@haskell.org> #13832: No parameter-validation in Control.Concurrent.setNumCapabilities -------------------------------------+------------------------------------- Reporter: AlistairWard | Owner: (none) Type: bug | Status: new Priority: low | Milestone: Component: Core | Version: 8.0.1 Libraries | Keywords: | Operating System: Linux setNumCapabilities | Architecture: x86 | Type of failure: Runtime crash Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- > ghci GHCi, version 7.6.3: 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> Control.Concurrent.setNumCapabilities $ negate 1 malloc: failed on request for 18446744073709551104 bytes; message: moreCapabilities The parameter is forwarded to the underlying C-function without validation, the runtime then crashes; no exception is thrown. This behaviour also exists in ghc 8.0.2 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jun 15 13:54:22 2017 From: ghc-devs at haskell.org (GHC) Date: Thu, 15 Jun 2017 13:54:22 -0000 Subject: [GHC] #13795: :kind! is not expanding type synonyms anymore In-Reply-To: <045.9bd0a404a46fb5b0930c49818b8cb45d@haskell.org> References: <045.9bd0a404a46fb5b0930c49818b8cb45d@haskell.org> Message-ID: <060.22309a77a0d201394fdabfa40611c472@haskell.org> #13795: :kind! is not expanding type synonyms anymore -------------------------------------+------------------------------------- Reporter: Hjulle | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: GHCi | Version: 8.0.2 Resolution: | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by vl.still): I found a possible workaround (usable more with appropriate HINT or GHC API functions such as Language.Haskell.Interpreter.normalizeType) and inconsistency in behavior of current GHC(i) (8.0.2): Let's have following type family: {{{#!hs type family Id a type instance Id a = a }}} now in GHCi: {{{ >λ= :kind! String String :: * = String >λ= :kind! Id String Id String :: * = [Char] >λ= :kind! Id String -> String Id String -> String :: * = [Char] -> String }}} So it seems that type synonyms are expanded as long as they are in subexpression of an expression with type family. I personally would appriciate in :kind! expanded type synonyms as well as type families. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jun 15 14:15:02 2017 From: ghc-devs at haskell.org (GHC) Date: Thu, 15 Jun 2017 14:15:02 -0000 Subject: [GHC] #13009: Hierarchical Module Structure for GHC In-Reply-To: <045.859215149771e4346ac45f933feca22e@haskell.org> References: <045.859215149771e4346ac45f933feca22e@haskell.org> Message-ID: <060.a1ae9feaff7615bf9856b8f6241f651c@haskell.org> #13009: Hierarchical Module Structure for GHC -------------------------------------+------------------------------------- Reporter: hsyl20 | Owner: hsyl20 Type: task | Status: patch Priority: low | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3647 Wiki Page: | ModuleDependencies/Hierarchical | -------------------------------------+------------------------------------- Comment (by hsyl20): The discussion about the renaming has started on Phab. I'm copying it here. simonpj: For example, I'd like to remove the IR/ level, and just have Cmm, Core etc. It doesn't pay its way in my view. simonmar: I agree with @simonpj that IR should go away for example. me: Considering the proposed hierarchy, I have been loosely following the old proposal on the wiki (ModuleDependencies/Hierarchical) but adapted it. I have iterated quite a few times and indeed I started without the IR level but it felt wrong for GHC.Haskell (isn't GHC all about Haskell?) and GHC.Core ("core" is misleading and I wouldn't think it is an IR if I wouldn't already know it is). Moreover I didn't want to pollute too much the top-level. In general I have tried to make module names meaningful and unambiguous, even to someone that is first exposed to them. For instance, just by looking at the outline (e.g., see current Haddock on http://hsyl20.fr/ghc_doc/), even if we don't know what FloatOut is, we know it's a transformation on Core IR. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jun 15 15:53:49 2017 From: ghc-devs at haskell.org (GHC) Date: Thu, 15 Jun 2017 15:53:49 -0000 Subject: [GHC] #13009: Hierarchical Module Structure for GHC In-Reply-To: <045.859215149771e4346ac45f933feca22e@haskell.org> References: <045.859215149771e4346ac45f933feca22e@haskell.org> Message-ID: <060.ace6a5e649b38a3b8eb876043772f4af@haskell.org> #13009: Hierarchical Module Structure for GHC -------------------------------------+------------------------------------- Reporter: hsyl20 | Owner: hsyl20 Type: task | Status: patch Priority: low | Milestone: Component: GHC API | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3647 Wiki Page: | ModuleDependencies/Hierarchical | -------------------------------------+------------------------------------- Changes (by hsyl20): * component: Compiler => GHC API -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jun 15 16:02:50 2017 From: ghc-devs at haskell.org (GHC) Date: Thu, 15 Jun 2017 16:02:50 -0000 Subject: [GHC] #13267: Constraint synonym instances In-Reply-To: <045.f8ed117474c8000ae242eae97e053b65@haskell.org> References: <045.f8ed117474c8000ae242eae97e053b65@haskell.org> Message-ID: <060.dbc122d71e7be128bbdbb520bb2d517e@haskell.org> #13267: Constraint synonym instances -------------------------------------+------------------------------------- Reporter: ezyang | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.2.1 Component: Compiler (Type | Version: 8.1 checker) | Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: GHC accepts | Test Case: invalid program | polykinds/T13267 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by niteria): I'd like to just note that https://github.com/niteria/dual- tree/blob/master/test/Test.hs now fails to build with: {{{ test/Test.hs:55:19: error: • Illegal instance for a type synonym A class instance must be for a class • In the stand-alone deriving instance for ‘Typeable1 Sum’ | 55 | deriving instance Typeable1 X.Sum | ^^^^^^^^^^^^^^^ test/Test.hs:56:19: error: • Illegal instance for a type synonym A class instance must be for a class • In the stand-alone deriving instance for ‘Typeable1 Product’ | 56 | deriving instance Typeable1 X.Product | ^^^^^^^^^^^^^^^^^^^ }}} I will attach a smaller example. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jun 15 16:03:52 2017 From: ghc-devs at haskell.org (GHC) Date: Thu, 15 Jun 2017 16:03:52 -0000 Subject: [GHC] #13267: Constraint synonym instances In-Reply-To: <045.f8ed117474c8000ae242eae97e053b65@haskell.org> References: <045.f8ed117474c8000ae242eae97e053b65@haskell.org> Message-ID: <060.b5b5e83516076d3bd659a4617c756086@haskell.org> #13267: Constraint synonym instances -------------------------------------+------------------------------------- Reporter: ezyang | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.2.1 Component: Compiler (Type | Version: 8.1 checker) | Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: GHC accepts | Test Case: invalid program | polykinds/T13267 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by niteria): * Attachment "A.hs" added. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jun 15 16:07:04 2017 From: ghc-devs at haskell.org (GHC) Date: Thu, 15 Jun 2017 16:07:04 -0000 Subject: [GHC] #13267: Constraint synonym instances In-Reply-To: <045.f8ed117474c8000ae242eae97e053b65@haskell.org> References: <045.f8ed117474c8000ae242eae97e053b65@haskell.org> Message-ID: <060.4e77e73d4513f731d3247f244757fe28@haskell.org> #13267: Constraint synonym instances -------------------------------------+------------------------------------- Reporter: ezyang | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.2.1 Component: Compiler (Type | Version: 8.1 checker) | Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: GHC accepts | Test Case: invalid program | polykinds/T13267 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): Certainly, since `Typeable1` is a constraint synonym for `Typeable` (since the 7.8 release, where `Typeable` became poly-kinded). But `Typeable1`, `Typeable2`, //et al.// have also been deprecated since 7.8 - surely you can just use `Typeable` instead? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jun 15 16:22:23 2017 From: ghc-devs at haskell.org (GHC) Date: Thu, 15 Jun 2017 16:22:23 -0000 Subject: [GHC] #12564: Type family in type pattern kind In-Reply-To: <048.93ccdd84c715d6e667e14d904b8a963f@haskell.org> References: <048.93ccdd84c715d6e667e14d904b8a963f@haskell.org> Message-ID: <063.292382fa4d3c6056330b3bf11ea375f4@haskell.org> #12564: Type family in type pattern kind -------------------------------------+------------------------------------- Reporter: int-index | Owner: goldfire Type: bug | Status: new Priority: high | Milestone: 8.4.1 Component: Compiler (Type | Version: 8.0.1 checker) | Keywords: TypeInType, Resolution: | TypeFamilies Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * cc: RyanGlScott (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jun 15 17:37:00 2017 From: ghc-devs at haskell.org (GHC) Date: Thu, 15 Jun 2017 17:37:00 -0000 Subject: [GHC] #13267: Constraint synonym instances In-Reply-To: <045.f8ed117474c8000ae242eae97e053b65@haskell.org> References: <045.f8ed117474c8000ae242eae97e053b65@haskell.org> Message-ID: <060.72d3f90bb89a6773aefa5613445f8e4c@haskell.org> #13267: Constraint synonym instances -------------------------------------+------------------------------------- Reporter: ezyang | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.2.1 Component: Compiler (Type | Version: 8.1 checker) | Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: GHC accepts | Test Case: invalid program | polykinds/T13267 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): (And perhaps we should consider removing `Typeable1`, `Typeable2`, etc. entirely?) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jun 15 23:49:26 2017 From: ghc-devs at haskell.org (GHC) Date: Thu, 15 Jun 2017 23:49:26 -0000 Subject: =?utf-8?b?UmU6IFtHSENdICMxMzYxNTogTm9uZGV0ZXJtaW5pc20gaW4g4oCY?= =?utf-8?q?pure=E2=80=99_function_w/_parallel_evaluation_=26_memo?= =?utf-8?q?_combinators?= In-Reply-To: <044.57733831351687fff6258688df1f42f7@haskell.org> References: <044.57733831351687fff6258688df1f42f7@haskell.org> Message-ID: <059.c67d6e31f323c476ed1bcd903fdbdf77@haskell.org> #13615: Nondeterminism in ‘pure’ function w/ parallel evaluation & memo combinators -------------------------------------+------------------------------------- Reporter: pacak | Owner: bgamari Type: bug | Status: new Priority: highest | Milestone: 8.2.1 Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by pacak): {{{ runST = unsafeDupablePerformIO -- more or less }}} > `unsafeDupablePerformIO`: This version of `unsafePerformIO` is more efficient because it omits the check that the IO is only being performed by a single thread. Basically "not to be used in multiple threads, we really mean it, look at the name" > `par`: Indicates that it may be beneficial to evaluate the first argument in parallel with the second. Basically "do things in multiple threads". The problem is `unsafeDupablePerformIO` is hidden in a bunch of different places. HashMaps, ByteStrings, etc... `par` is less frequent but not used directly either but it's also out there. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 16 03:56:08 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 16 Jun 2017 03:56:08 -0000 Subject: [GHC] #11829: C++ does not catch exceptions when used with Haskell-main and linked by ghc In-Reply-To: <041.08b08e181b7a4c97ec0ab8f67992afaf@haskell.org> References: <041.08b08e181b7a4c97ec0ab8f67992afaf@haskell.org> Message-ID: <056.be3fee7a7bd16608a2aa5cd6bab95547@haskell.org> #11829: C++ does not catch exceptions when used with Haskell-main and linked by ghc -------------------------------------+------------------------------------- Reporter: pl | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Runtime System | Version: 7.10.3 Resolution: | Keywords: c++ | exceptions Operating System: MacOS X | Architecture: | Unknown/Multiple Type of failure: Runtime crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by mtolly): This is still the case on macOS 10.12.5 and GHC 8.0.2. By examining the `ld` call from `g++` and experimenting, I discovered the fix is a flag that Clang's linker needs. Place this in the cabal file executable section: {{{ ld-options: -lto_library }}} Or use the following flag for GHC: {{{ ghc (source files) -lstdc++ -optl-lto_library }}} In the cabal file this amusingly parses the flag wrong and produces the incorrect advice: {{{ Warning: Instead of 'ld-options: -lto_library' use 'extra-libraries: to_library' }}} and it also prints the message from #5019 for some reason: {{{ ld: warning: could not create compact unwind for _ffi_call_unix64: does not use RBP or RSP based frame }}} [http://llvm.org/docs/LinkTimeOptimization.html Here is some info on what the flag does], but I don't quite understand how it is connected to exceptions. And [https://reviews.llvm.org/D25932 this page] suggests that a newer Clang will supply the flag automatically. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 16 07:32:58 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 16 Jun 2017 07:32:58 -0000 Subject: [GHC] #13833: Instances with GHC.TypeLits.Nat/Symbol should be possible without FlexibleInstances. Message-ID: <045.899fdc291fee22417bd4b56eb02e56da@haskell.org> #13833: Instances with GHC.TypeLits.Nat/Symbol should be possible without FlexibleInstances. -------------------------------------+------------------------------------- Reporter: Hjulle | Owner: (none) Type: bug | Status: new Priority: low | Milestone: Component: Compiler | Version: 8.0.2 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- Yes I know, `0` and `"B"` are not technically type constructors, but it's as close as you can get for the kinds Nat and Symbol. Test cases: {{{#!hs {-# LANGUAGE DataKinds, KindSignatures #-} import GHC.TypeLits (Nat, Symbol) class A (n::Nat) instance A 0 class B (s::Symbol) instance B "B" }}} Result: {{{ A.hs:6:10: error: • Illegal instance declaration for ‘A 0’ (All instance types must be of the form (T a1 ... an) where a1 ... an are *distinct type variables*, and each type variable appears at most once in the instance head. Use FlexibleInstances if you want to disable this.) • In the instance declaration for ‘A 0’ A.hs:9:10: error: • Illegal instance declaration for ‘B "B"’ (All instance types must be of the form (T a1 ... an) where a1 ... an are *distinct type variables*, and each type variable appears at most once in the instance head. Use FlexibleInstances if you want to disable this.) • In the instance declaration for ‘B "B"’ }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 16 09:04:45 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 16 Jun 2017 09:04:45 -0000 Subject: [GHC] #8697: Type rationals In-Reply-To: <050.5a686d61530f3e6b07142cffaf979586@haskell.org> References: <050.5a686d61530f3e6b07142cffaf979586@haskell.org> Message-ID: <065.c83ca6f0d79c3db9a1b7ec64967b7407@haskell.org> #8697: Type rationals -------------------------------------+------------------------------------- Reporter: MikeIzbicki | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.6.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by dredozubov): I want to say that I would personally like to see type literals for Integers and Rationals. You can always express Rationals as a library, for example, but type levels DSLs can't be really useful without a bit of syntactic sugar to support them. @adamgundry Considering the direction towards dependent types, I don't think it presents too big of a problem. Type language would have to support a wider array of literals at some anyway. For the state we're in today, singleton types and type literals compliment each other to create an expressive type level DSLs, as can be seen in this library, for an example: https://github.com/dredozubov/schematic/blob/master/src/Data/Schematic/Schema.hs -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 16 10:57:57 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 16 Jun 2017 10:57:57 -0000 Subject: [GHC] #13009: Hierarchical Module Structure for GHC In-Reply-To: <045.859215149771e4346ac45f933feca22e@haskell.org> References: <045.859215149771e4346ac45f933feca22e@haskell.org> Message-ID: <060.e6e8b8200420cfac76d02dfdcbbc7990@haskell.org> #13009: Hierarchical Module Structure for GHC -------------------------------------+------------------------------------- Reporter: hsyl20 | Owner: hsyl20 Type: task | Status: patch Priority: low | Milestone: Component: GHC API | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3647 Wiki Page: | ModuleDependencies/Hierarchical | -------------------------------------+------------------------------------- Changes (by michalt): * cc: michalt (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 16 13:29:05 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 16 Jun 2017 13:29:05 -0000 Subject: [GHC] #13009: Hierarchical Module Structure for GHC In-Reply-To: <045.859215149771e4346ac45f933feca22e@haskell.org> References: <045.859215149771e4346ac45f933feca22e@haskell.org> Message-ID: <060.d9cd3fedb5c67ed1bfcd3dac0724e8bf@haskell.org> #13009: Hierarchical Module Structure for GHC -------------------------------------+------------------------------------- Reporter: hsyl20 | Owner: hsyl20 Type: task | Status: patch Priority: low | Milestone: Component: GHC API | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3647 Wiki Page: | ModuleDependencies/Hierarchical | -------------------------------------+------------------------------------- Comment (by darchon): Having a couple packages on released on hackage that use the GHC API, all of which are (actively) maintained, I do hope that there will be a solution that allows me to support multiple versions of GHC without having to add even more CPP #ifdefs. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 16 13:37:15 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 16 Jun 2017 13:37:15 -0000 Subject: =?utf-8?b?UmU6IFtHSENdICMxMzYxNTogTm9uZGV0ZXJtaW5pc20gaW4g4oCY?= =?utf-8?q?pure=E2=80=99_function_w/_parallel_evaluation_=26_memo?= =?utf-8?q?_combinators?= In-Reply-To: <044.57733831351687fff6258688df1f42f7@haskell.org> References: <044.57733831351687fff6258688df1f42f7@haskell.org> Message-ID: <059.bea49835bc662235a6b74efbfcca028f@haskell.org> #13615: Nondeterminism in ‘pure’ function w/ parallel evaluation & memo combinators -------------------------------------+------------------------------------- Reporter: pacak | Owner: bgamari Type: bug | Status: new Priority: highest | Milestone: 8.2.1 Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by andrewthad): pacak, it should in general be safe to duplicate an ST computation on multiple threads. For IO, it's a problem because mutable variables can come from outside of the IO computation. Something like `unsafeDupablePerformIO (modifyIORef ...)` is bad because for this reason. But, with ST, variables cannot escape the scope of the computation, so it should be safe. There is no way to write the ST equivalent of the expression I just gave. You would instead have to write: `runST (do {r <- newSTRef 5; modifySTRef r ...;})`, but this should be safe to duplicate, since each thread ends up with its own STRef (no sharing of the reference across threads). Also worth mentioning is that GHC cannot float out the call to `newSTRef` because of how the state token is threaded through the computation in `ST`s `Monad` instance. In #11760, it was discovered that lazy ST was unsound because it allows you to create pure expressions that capture mutable variables. When one of these expression is evaluated on two capabilities simultaneously, we get nondeterministic results. According to people on that thread, strict ST should not have the same problem. I don't totally understand why. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 16 14:05:23 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 16 Jun 2017 14:05:23 -0000 Subject: [GHC] #13009: Hierarchical Module Structure for GHC In-Reply-To: <045.859215149771e4346ac45f933feca22e@haskell.org> References: <045.859215149771e4346ac45f933feca22e@haskell.org> Message-ID: <060.2624b89917b0a9421b0f7bfc930ac1aa@haskell.org> #13009: Hierarchical Module Structure for GHC -------------------------------------+------------------------------------- Reporter: hsyl20 | Owner: hsyl20 Type: task | Status: patch Priority: low | Milestone: Component: GHC API | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3647 Wiki Page: | ModuleDependencies/Hierarchical | -------------------------------------+------------------------------------- Comment (by mpickering): I think the benefits of this are very marginal and the costs quite high for package maintainers. In general I don't like long module names but that is also a matter of preference. It is usual (at least in my projects) to import modules from GHC as qualified which avoids the problem with clashing module names. To take your example of `FloatOut`, it's already in the folder called `simplCore`. The modules are organised in a directory hierarchy just not a namespace hierarchy. It seems the benefit is for browsing documentation in haddock, but it is already hard to use haddock with GHC as not that many functions have haddock comments and you need to read the Notes in order to understand everything. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 16 14:47:39 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 16 Jun 2017 14:47:39 -0000 Subject: [GHC] #11954: Associated pattern synonyms not included in haddock In-Reply-To: <046.dee795066f70760dedef2b550cf6d5e0@haskell.org> References: <046.dee795066f70760dedef2b550cf6d5e0@haskell.org> Message-ID: <061.b05e9b024079c7c0ce22b9581588c26c@haskell.org> #11954: Associated pattern synonyms not included in haddock -------------------------------------+------------------------------------- Reporter: darchon | Owner: (none) Type: bug | Status: patch Priority: normal | Milestone: 8.2.1 Component: Compiler | Version: 8.0.1-rc3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by darchon): * milestone: 8.4.1 => 8.2.1 Comment: Hopefully https://github.com/haskell/haddock/commit/87c551fc668b9251f2647cce8772f205e1cee154, which is in haddock's master branch, can still be included for the 8.2.1 release. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 16 15:19:23 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 16 Jun 2017 15:19:23 -0000 Subject: [GHC] #13009: Hierarchical Module Structure for GHC In-Reply-To: <045.859215149771e4346ac45f933feca22e@haskell.org> References: <045.859215149771e4346ac45f933feca22e@haskell.org> Message-ID: <060.2e9983386e6fdb850b0325b226146f78@haskell.org> #13009: Hierarchical Module Structure for GHC -------------------------------------+------------------------------------- Reporter: hsyl20 | Owner: hsyl20 Type: task | Status: patch Priority: low | Milestone: Component: GHC API | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3647 Wiki Page: | ModuleDependencies/Hierarchical | -------------------------------------+------------------------------------- Comment (by bgamari): > I think the benefits of this are very marginal and the costs quite high for package maintainers. While I may agree that the benefits are nothing earth-shattering, I think we aren't yet in a position to judge the costs. Afterall, it has been proposed that we provide module re-exports, which would make this largely transparent to packages. I'd imagine that we would retain these for the usual three releases and then drop them. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 16 15:25:29 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 16 Jun 2017 15:25:29 -0000 Subject: [GHC] #13009: Hierarchical Module Structure for GHC In-Reply-To: <045.859215149771e4346ac45f933feca22e@haskell.org> References: <045.859215149771e4346ac45f933feca22e@haskell.org> Message-ID: <060.669e0004f10578016a5bbc28557d8213@haskell.org> #13009: Hierarchical Module Structure for GHC -------------------------------------+------------------------------------- Reporter: hsyl20 | Owner: hsyl20 Type: task | Status: patch Priority: low | Milestone: Component: GHC API | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3647 Wiki Page: | ModuleDependencies/Hierarchical | -------------------------------------+------------------------------------- Comment (by bgamari): On the matter of the concrete renaming, I would say that unnecessary renaming of GHC's traditional nomenclature should be avoided. That is, renaming the desugarer to `HaskellToCore` is in my opinion going to cause far more harm than good. These names are scattered throughout commit messages, documentation, comments, and the wiki and it's not practical to rename them all. While it may be true that the function of the "desugarer" isn't immediately clear to newcomers, I would argue that this nomenclature is a tiny bit to learn relative to the rest of GHC, and that inconsistent naming will make things even harder. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 16 15:53:54 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 16 Jun 2017 15:53:54 -0000 Subject: [GHC] #13009: Hierarchical Module Structure for GHC In-Reply-To: <045.859215149771e4346ac45f933feca22e@haskell.org> References: <045.859215149771e4346ac45f933feca22e@haskell.org> Message-ID: <060.5bd40b8baea288532693d3869d689ea8@haskell.org> #13009: Hierarchical Module Structure for GHC -------------------------------------+------------------------------------- Reporter: hsyl20 | Owner: hsyl20 Type: task | Status: patch Priority: low | Milestone: Component: GHC API | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3647 Wiki Page: | ModuleDependencies/Hierarchical | -------------------------------------+------------------------------------- Comment (by Phyx-): Replying to [comment:10 mpickering]: > I think the benefits of this are very marginal and the costs quite high for package maintainers. I also don't really see many benefits from this, but also think the cost is high for GHC developers. Long standing patches and branches need to be re-based and imports renamed. While I appreciate that it's a one time cost, it's a very painful one. That aside, the split between `ghc/ghci` and `compiler/GHC.Interactive` seems weird. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 16 16:01:38 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 16 Jun 2017 16:01:38 -0000 Subject: [GHC] #13834: Error cascade with type applications Message-ID: <049.1249ca55bb94d4476098b14993c34065@haskell.org> #13834: Error cascade with type applications -------------------------------------+------------------------------------- Reporter: mpickering | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Keywords: newcomer, | Operating System: Unknown/Multiple TypeApplications | Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- Using type applications with an out of scope identifier causes an unfortunate error cascade. {{{ foo = notInScope @Bool }}} Leads to the right out of scope error but also an error about using type application when `notInScope` is not a polytype. I think the second error should be suppressed. {{{ t.hs:4:7: error: Variable not in scope: notInScope | 4 | foo = notInScope @Bool | ^^^^^^^^^^ t.hs:4:7: error: • Cannot apply expression of type ‘t1’ to a visible type argument ‘Bool’ notInScope • In the expression: notInScope @Bool In an equation for ‘foo’: foo = notInScope @Bool | 4 | foo = notInScope @Bool | ^^^^^^^^^^^^^^^^ }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 16 16:25:45 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 16 Jun 2017 16:25:45 -0000 Subject: =?utf-8?b?UmU6IFtHSENdICMxMzYxNTogTm9uZGV0ZXJtaW5pc20gaW4g4oCY?= =?utf-8?q?pure=E2=80=99_function_w/_parallel_evaluation_=26_memo?= =?utf-8?q?_combinators?= In-Reply-To: <044.57733831351687fff6258688df1f42f7@haskell.org> References: <044.57733831351687fff6258688df1f42f7@haskell.org> Message-ID: <059.de386073515f3975f6e5d631b280bfb1@haskell.org> #13615: Nondeterminism in ‘pure’ function w/ parallel evaluation & memo combinators -------------------------------------+------------------------------------- Reporter: pacak | Owner: bgamari Type: bug | Status: new Priority: highest | Milestone: 8.2.1 Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): > According to people on that thread, strict ST should not have the same problem. I don't totally understand why. In the case of strict ST all effects should be executed before we produce the result. This means that there should be no chance of entering any thunk arising from the `ST` block producing effects, meaning that multiple entry should pose no thread to correctness. However, if my hypothesis from comment:36 holds then it is indeed possible for the garbage collector to suspend a computation before all effects have taken place. This places us in a position where multiple-entry will indeed cause effects to be performed multiple times. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 16 17:01:47 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 16 Jun 2017 17:01:47 -0000 Subject: [GHC] #13835: ghci with ":set +t" should print type before starting evaluation Message-ID: <049.babc2baa39ced2b9a895aa8b0723cb93@haskell.org> #13835: ghci with ":set +t" should print type before starting evaluation -------------------------------------+------------------------------------- Reporter: j.waldmann | Owner: (none) Type: feature | Status: new request | Priority: normal | Milestone: Component: GHCi | Version: Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- Not an actual bug, but questionable design perhaps. I think this is backwards, as static analysis comes before evaluation, not after: {{{ Prelude> :set +t Prelude> reverse [True] [True] it :: [Bool] }}} When evaluation raises an exception, no type is printed. {{{ Prelude> :set +t Prelude> True && undefined *** Exception: Prelude.undefined CallStack (from HasCallStack): error, called at libraries/base/GHC/Err.hs:79:14 in base:GHC.Err undefined, called at :8:9 in interactive:Ghci4 }}} For teaching (and for my own sanity) I'd much prefer output in logical succession. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 16 18:52:33 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 16 Jun 2017 18:52:33 -0000 Subject: [GHC] #13835: ghci with ":set +t" should print type before starting evaluation In-Reply-To: <049.babc2baa39ced2b9a895aa8b0723cb93@haskell.org> References: <049.babc2baa39ced2b9a895aa8b0723cb93@haskell.org> Message-ID: <064.3866ebf8df217e7b26346f2983522cb6@haskell.org> #13835: ghci with ":set +t" should print type before starting evaluation -------------------------------------+------------------------------------- Reporter: j.waldmann | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: Component: GHCi | Version: Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by vanto): Hello,\\ If you write this, you have\\ {{{ Prelude> :set + t Prelude> let y = reverse [True] y :: [Bool] Prelude> y [True] it :: [Bool] Prelude> let z = True && undefined z :: Bool Prelude> z *** Exception: Prelude.undefined CallStack (from HasCallStack): error, called at libraries\base\GHC\Err.hs:79:14 in base:GHC.Err undefined, called at :8:17 in interactive:Ghci6 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 16 19:10:07 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 16 Jun 2017 19:10:07 -0000 Subject: [GHC] #9630: compile-time performance regression (probably due to Generics) In-Reply-To: <042.a529e5f70870528e7f8796a28ce82a84@haskell.org> References: <042.a529e5f70870528e7f8796a28ce82a84@haskell.org> Message-ID: <057.0f6d181b9b32be1590f2ec9f64203b5f@haskell.org> #9630: compile-time performance regression (probably due to Generics) -------------------------------------+------------------------------------- Reporter: hvr | Owner: dfeuer Type: bug | Status: new Priority: high | Milestone: 8.2.1 Component: Compiler | Version: 7.9 Resolution: | Keywords: deriving- | perf, Generics Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: #9583, #10293, | Differential Rev(s): #13059, #10818 | Wiki Page: | -------------------------------------+------------------------------------- Comment (by dfeuer): Hmmmm... While 2b74bd9d8b4c6b20f3e8d9ada12e7db645cc3c19 seems to improve matters considerably, it doesn't fix the whole issue. ezyang's reproduction in comment:22 can be modified to make things blow up after the commit, and as far back as 7.8 at least. Specifically: * Increase the size of the definition of `T`, leaving it in the `Gen` module. * Move the definition of `tput` to a separate `GenSpec` module. This will lead to simplifier tick exhaustion. If the definition of `T` (or even just the derivation of `Generic T`) is moved to `GenSpec`, then compilation succeeds. The number of terms seems to blow up several simplifier passes after specialization. I don't yet know why, but it smells like inlining. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 16 19:19:03 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 16 Jun 2017 19:19:03 -0000 Subject: [GHC] #13832: No parameter-validation in Control.Concurrent.setNumCapabilities In-Reply-To: <051.3d60dff1f88e30b72e07c48763136ae0@haskell.org> References: <051.3d60dff1f88e30b72e07c48763136ae0@haskell.org> Message-ID: <066.19b01736933d994c94d99587cef672c9@haskell.org> #13832: No parameter-validation in Control.Concurrent.setNumCapabilities -------------------------------------+------------------------------------- Reporter: AlistairWard | Owner: (none) Type: bug | Status: new Priority: low | Milestone: Component: Core Libraries | Version: 8.0.1 Resolution: | Keywords: | setNumCapabilities Operating System: Linux | Architecture: x86 Type of failure: Runtime crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"9849403147b584ff160daeb4f13bf36adb2bab2e/ghc" 9849403/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="9849403147b584ff160daeb4f13bf36adb2bab2e" base: Validate input in setNumCapabilities Test Plan: validate Reviewers: austin, hvr, erikd, simonmar Subscribers: rwbarton, thomie GHC Trac Issues: #13832 Differential Revision: https://phabricator.haskell.org/D3652 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 16 19:21:12 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 16 Jun 2017 19:21:12 -0000 Subject: [GHC] #13832: No parameter-validation in Control.Concurrent.setNumCapabilities In-Reply-To: <051.3d60dff1f88e30b72e07c48763136ae0@haskell.org> References: <051.3d60dff1f88e30b72e07c48763136ae0@haskell.org> Message-ID: <066.5869e934cdde27e323a7d902b0edef4b@haskell.org> #13832: No parameter-validation in Control.Concurrent.setNumCapabilities -------------------------------------+------------------------------------- Reporter: AlistairWard | Owner: (none) Type: bug | Status: merge Priority: low | Milestone: 8.2.1 Component: Core Libraries | Version: 8.0.1 Resolution: | Keywords: | setNumCapabilities Operating System: Linux | Architecture: x86 Type of failure: Runtime crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => merge * milestone: => 8.2.1 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 16 19:21:35 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 16 Jun 2017 19:21:35 -0000 Subject: [GHC] #13832: No parameter-validation in Control.Concurrent.setNumCapabilities In-Reply-To: <051.3d60dff1f88e30b72e07c48763136ae0@haskell.org> References: <051.3d60dff1f88e30b72e07c48763136ae0@haskell.org> Message-ID: <066.e26141d868e5330814593fb98448c3d1@haskell.org> #13832: No parameter-validation in Control.Concurrent.setNumCapabilities -------------------------------------+------------------------------------- Reporter: AlistairWard | Owner: (none) Type: bug | Status: merge Priority: low | Milestone: 8.2.1 Component: Core Libraries | Version: 8.0.1 Resolution: | Keywords: | setNumCapabilities Operating System: Linux | Architecture: x86 Type of failure: Runtime crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Description changed by bgamari: @@ -0,0 +1,1 @@ + {{{ @@ -9,0 +10,1 @@ + }}} New description: {{{ > ghci GHCi, version 7.6.3: 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> Control.Concurrent.setNumCapabilities $ negate 1 malloc: failed on request for 18446744073709551104 bytes; message: moreCapabilities }}} The parameter is forwarded to the underlying C-function without validation, the runtime then crashes; no exception is thrown. This behaviour also exists in ghc 8.0.2 -- -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 16 19:28:08 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 16 Jun 2017 19:28:08 -0000 Subject: [GHC] #9630: compile-time performance regression (probably due to Generics) In-Reply-To: <042.a529e5f70870528e7f8796a28ce82a84@haskell.org> References: <042.a529e5f70870528e7f8796a28ce82a84@haskell.org> Message-ID: <057.e551d4a4ee5563ba9b441593c4a2be5c@haskell.org> #9630: compile-time performance regression (probably due to Generics) -------------------------------------+------------------------------------- Reporter: hvr | Owner: dfeuer Type: bug | Status: new Priority: high | Milestone: 8.2.1 Component: Compiler | Version: 7.9 Resolution: | Keywords: deriving- | perf, Generics Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: #9583, #10293, | Differential Rev(s): #13059, #10818 | Wiki Page: | -------------------------------------+------------------------------------- Comment (by dfeuer): Actually, push that all the way back to 7.4.1, which produces a warning instead of an error for tick exhaustion. I don't have easy access to any earlier versions. So I guess ''part'' of this problem is a lot older than previously realized. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 16 19:49:46 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 16 Jun 2017 19:49:46 -0000 Subject: [GHC] #13836: Some event log events won't be flushed if capability count decreased with setNumCapabitilies Message-ID: <046.e07128837fcde826a9a245793a21e443@haskell.org> #13836: Some event log events won't be flushed if capability count decreased with setNumCapabitilies -------------------------------------+------------------------------------- Reporter: bgamari | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Runtime | Version: 8.0.1 System | Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- Currently the eventlog code assumes that there have been at most `n_capabilities` capabilities at the time of cleanup. This may not hold in the event that the capability count was decreased using `setNumCapabilities`. This means that some `EventBuf`s won't be flushed when the program terminates. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 16 20:03:21 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 16 Jun 2017 20:03:21 -0000 Subject: [GHC] #13836: Some event log events won't be flushed if capability count decreased with setNumCapabitilies In-Reply-To: <046.e07128837fcde826a9a245793a21e443@haskell.org> References: <046.e07128837fcde826a9a245793a21e443@haskell.org> Message-ID: <061.17d247116560097e9e248fe847fba1d5@haskell.org> #13836: Some event log events won't be flushed if capability count decreased with setNumCapabitilies -------------------------------------+------------------------------------- Reporter: bgamari | Owner: (none) Type: bug | Status: patch Priority: normal | Milestone: Component: Runtime System | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3654 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => patch * differential: => Phab:D3654 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 16 20:04:46 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 16 Jun 2017 20:04:46 -0000 Subject: [GHC] #13830: '+RTS -s' gives incorrect value for work balance in some cases In-Reply-To: <043.14e010bc8c8133d891369e32e6e80a21@haskell.org> References: <043.14e010bc8c8133d891369e32e6e80a21@haskell.org> Message-ID: <058.e5e5a91026eb1fec6b0f2aff027e36f1@haskell.org> #13830: '+RTS -s' gives incorrect value for work balance in some cases -------------------------------------+------------------------------------- Reporter: duog | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Runtime System | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Debugging | Unknown/Multiple information is incorrect | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): Mmm, I suspect there are a lot of these sorts of issues since dynamically changing the number of capabilities was something of an afterthought AFAIK. See #13836 for another which I spotted a few days ago. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 16 20:13:13 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 16 Jun 2017 20:13:13 -0000 Subject: [GHC] #13827: "What AbsBinds means" is a pretty confusing doc comment In-Reply-To: <046.d6811ad66cde747388ca38ca27c2378f@haskell.org> References: <046.d6811ad66cde747388ca38ca27c2378f@haskell.org> Message-ID: <061.06eb934813955cb21d3e28035c9e70b0@haskell.org> #13827: "What AbsBinds means" is a pretty confusing doc comment -------------------------------------+------------------------------------- Reporter: literon | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Documentation | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): Have you seen `Note [AbsBinds]` also in that note? It might help clear things up a bit. That being said, I agree that `Note [What AbsBinds means]` is quite terse. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 16 20:33:28 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 16 Jun 2017 20:33:28 -0000 Subject: [GHC] #13822: GHC not using injectivity? In-Reply-To: <051.2a3d251c10227c1a71de0d444bf548f8@haskell.org> References: <051.2a3d251c10227c1a71de0d444bf548f8@haskell.org> Message-ID: <066.b6032409babf2b43e2056060d159e1ea@haskell.org> #13822: GHC not using injectivity? -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.2.1 Component: Compiler | Version: 8.0.1 Resolution: fixed | Keywords: | InjectiveFamilies, TypeInType Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | typecheck/should_compile/T13822 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * testcase: => typecheck/should_compile/T13822 * milestone: => 8.2.1 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 16 20:39:27 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 16 Jun 2017 20:39:27 -0000 Subject: [GHC] #13426: compile-time memory-usage regression for DynFlags between GHC 8.0 and GHC 8.2 In-Reply-To: <042.588059ee1290b666bd7f0947c071e1ff@haskell.org> References: <042.588059ee1290b666bd7f0947c071e1ff@haskell.org> Message-ID: <057.e47b962e9ae73e87006e6b801cff45bd@haskell.org> #13426: compile-time memory-usage regression for DynFlags between GHC 8.0 and GHC 8.2 -------------------------------------+------------------------------------- Reporter: hvr | Owner: (none) Type: bug | Status: new Priority: high | Milestone: 8.2.1 Component: Compiler | Version: 8.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3399, Wiki Page: | Phab:D3400, Phab:D3421 -------------------------------------+------------------------------------- Comment (by bgamari): dfeuer will need to comment on what specifically "some cases" refers to, but the patch in comment:42 removes some `seq`s which don't appear to be necessary to prevent thunk leaks. I would expect that this did have a positive impact on compiler speed, but in practice this effect [[https://perf.haskell.org/ghc/#revision/2088d0be17dccfa91a4759bdbb20faae77c8dbed|appears]] to be too small to measure. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 16 20:43:22 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 16 Jun 2017 20:43:22 -0000 Subject: [GHC] #13587: addTopDecls fails with typed Template Haskell In-Reply-To: <048.1e9cb82827e3acfaa8c4e1f0f4c12487@haskell.org> References: <048.1e9cb82827e3acfaa8c4e1f0f4c12487@haskell.org> Message-ID: <063.8381faa8a263b982a48b7e41f10b6a82@haskell.org> #13587: addTopDecls fails with typed Template Haskell -------------------------------------+------------------------------------- Reporter: tmcdonell | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 8.2.1-rc1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * cc: simonpj, goldfire (added) Comment: I'm afraid not. I've CC'd Simon and Richard, both of whom know more about TH than me. That being said, if my suspicion from comment:5 is correct then this may be non-trivial to fix properly. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 16 20:45:57 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 16 Jun 2017 20:45:57 -0000 Subject: [GHC] #13821: bindings for unlifted types are allowed in .hs-boot files and .hsig files In-Reply-To: <043.23e5a07809642797cc00f131ea2af984@haskell.org> References: <043.23e5a07809642797cc00f131ea2af984@haskell.org> Message-ID: <058.aacea3663bcb02c2ef6f8ce01d9f9c15@haskell.org> #13821: bindings for unlifted types are allowed in .hs-boot files and .hsig files -------------------------------------+------------------------------------- Reporter: duog | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.1-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: GHC accepts | Test Case: invalid program | typecheck/should_fail/T13821 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * testcase: => typecheck/should_fail/T13821 Comment: Desugaring does seem like a strange time to perform this check. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 16 20:47:12 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 16 Jun 2017 20:47:12 -0000 Subject: [GHC] #9630: compile-time performance regression (probably due to Generics) In-Reply-To: <042.a529e5f70870528e7f8796a28ce82a84@haskell.org> References: <042.a529e5f70870528e7f8796a28ce82a84@haskell.org> Message-ID: <057.cb7202cf5f7e6f11d1b326f4e7166c0e@haskell.org> #9630: compile-time performance regression (probably due to Generics) -------------------------------------+------------------------------------- Reporter: hvr | Owner: dfeuer Type: bug | Status: new Priority: high | Milestone: 8.2.1 Component: Compiler | Version: 7.9 Resolution: | Keywords: deriving- | perf, Generics Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: #9583, #10293, | Differential Rev(s): Phab:D3656 #13059, #10818 | Wiki Page: | -------------------------------------+------------------------------------- Changes (by dfeuer): * differential: => Phab:D3656 Comment: I've added a test demonstrating improvement from the specializer change. It's not as precise as I'd like. A variation (moving the definition of `T` into the `T9630a` module while leaving the specialization in `T9630`) has more dramatic effects, with simplifier tick exhaustion in the older GHC. But as mentioned, a similar modification of Edward's test case does ''not'' see any improvement. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 16 21:02:13 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 16 Jun 2017 21:02:13 -0000 Subject: [GHC] #13832: No parameter-validation in Control.Concurrent.setNumCapabilities In-Reply-To: <051.3d60dff1f88e30b72e07c48763136ae0@haskell.org> References: <051.3d60dff1f88e30b72e07c48763136ae0@haskell.org> Message-ID: <066.70b57aab5e69bad2a432e24769eb6477@haskell.org> #13832: No parameter-validation in Control.Concurrent.setNumCapabilities -------------------------------------+------------------------------------- Reporter: AlistairWard | Owner: (none) Type: bug | Status: closed Priority: low | Milestone: 8.2.1 Component: Core Libraries | Version: 8.0.1 Resolution: fixed | Keywords: | setNumCapabilities Operating System: Linux | Architecture: x86 Type of failure: Runtime crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: merge => closed * resolution: => fixed Comment: Merged to `ghc-8.2` as a4e782087ae0df211f8d48c11ded0b1dd81f40a4. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 16 21:02:35 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 16 Jun 2017 21:02:35 -0000 Subject: [GHC] #13807: GHC 8.2 nondeterministic with foreign imports In-Reply-To: <046.b74945b333405c65044cabd09b1ff21f@haskell.org> References: <046.b74945b333405c65044cabd09b1ff21f@haskell.org> Message-ID: <061.076df9fbad10d01259290c595e6b93da@haskell.org> #13807: GHC 8.2 nondeterministic with foreign imports -------------------------------------+------------------------------------- Reporter: niteria | Owner: niteria Type: bug | Status: closed Priority: high | Milestone: 8.2.1 Component: Compiler | Version: 8.2.1-rc2 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: merge => closed * resolution: => fixed Comment: Merged to `ghc-8.2` as 40f4efb18c12d42d7ac735224e105bd177fe0e16. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 16 21:03:18 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 16 Jun 2017 21:03:18 -0000 Subject: [GHC] #13791: Document allowed syntax in WARNING and DEPRECATED pragmas In-Reply-To: <046.d7785f3c9a9f9afccfdc542d40ba4787@haskell.org> References: <046.d7785f3c9a9f9afccfdc542d40ba4787@haskell.org> Message-ID: <061.3bd27d372d3ed08c33fd91fed9294623@haskell.org> #13791: Document allowed syntax in WARNING and DEPRECATED pragmas -------------------------------------+------------------------------------- Reporter: phischu | Owner: (none) Type: bug | Status: closed Priority: lowest | Milestone: 8.2.1 Component: Compiler | Version: 8.0.2 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Documentation | Unknown/Multiple bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): Merged to `ghc-8.2` as d8794aa582687846178a0b11604b736212cbf936. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 16 21:03:44 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 16 Jun 2017 21:03:44 -0000 Subject: [GHC] #13751: Runtime crash with <> after concurrent stressing of STM computations In-Reply-To: <046.2e620bb56fd39fe88732c85fa515dde8@haskell.org> References: <046.2e620bb56fd39fe88732c85fa515dde8@haskell.org> Message-ID: <061.8796ee204c38b58e327c2956faca8be1@haskell.org> #13751: Runtime crash with <> after concurrent stressing of STM computations -------------------------------------+------------------------------------- Reporter: literon | Owner: simonmar Type: bug | Status: closed Priority: highest | Milestone: 8.2.1 Component: Runtime System | Version: 8.0.2 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Runtime crash | Test Case: Blocked By: | Blocking: Related Tickets: 10414 | Differential Rev(s): Phab:D3630 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: merge => closed * resolution: => fixed Comment: Merged to `ghc-8.2` as 62a4f066e8783f9c5f2bbaad37464e79711accfa. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 16 21:05:16 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 16 Jun 2017 21:05:16 -0000 Subject: [GHC] #13708: Panic! (the "impossible" happened) bug in GHC 8.2.1 rc2 In-Reply-To: <044.2693b478252b11f06ab341e229ae44a3@haskell.org> References: <044.2693b478252b11f06ab341e229ae44a3@haskell.org> Message-ID: <059.8440c10943cdfd9e73b76b888e3dabd0@haskell.org> #13708: Panic! (the "impossible" happened) bug in GHC 8.2.1 rc2 -------------------------------------+------------------------------------- Reporter: deech | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.2.1 Component: Compiler | Version: 8.2.1-rc2 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | simplCore/should_compile/T13708 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: merge => closed Comment: Merged to `ghc-8.2` in c7d809928d87a7a54bcea6badea3e7ee5f7181db but marked test as `expect_broken` due to comment:13. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 16 21:05:52 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 16 Jun 2017 21:05:52 -0000 Subject: [GHC] #13691: Bump time submodule In-Reply-To: <046.7033f0ecc0a7c3600b088ca823c99a67@haskell.org> References: <046.7033f0ecc0a7c3600b088ca823c99a67@haskell.org> Message-ID: <061.8f1bb90e2d3873371c7d75794d1fe9c5@haskell.org> #13691: Bump time submodule -------------------------------------+------------------------------------- Reporter: bgamari | Owner: (none) Type: task | Status: closed Priority: highest | Milestone: 8.2.1 Component: Compiler | Version: 8.0.1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => closed * resolution: => fixed Comment: Bumped in a5e045af9b51da43b7e743134fafedf56ae4f7e5. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 16 21:06:42 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 16 Jun 2017 21:06:42 -0000 Subject: [GHC] #9630: compile-time performance regression (probably due to Generics) In-Reply-To: <042.a529e5f70870528e7f8796a28ce82a84@haskell.org> References: <042.a529e5f70870528e7f8796a28ce82a84@haskell.org> Message-ID: <057.f3839bf305059abf3548aab9514dc221@haskell.org> #9630: compile-time performance regression (probably due to Generics) -------------------------------------+------------------------------------- Reporter: hvr | Owner: dfeuer Type: bug | Status: new Priority: high | Milestone: 8.2.1 Component: Compiler | Version: 7.9 Resolution: | Keywords: deriving- | perf, Generics Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: #9583, #10293, | Differential Rev(s): Phab:D3656 #13059, #10818 | Wiki Page: | -------------------------------------+------------------------------------- Comment (by dfeuer): FYI, the case that fails with tick exhaustion for (apparently) absolutely everything from 7.4 onward is [https://gist.github.com/treeowl/ca72b86ea4593e784e61b03ff28e26c7 in this gist]. Ryan says it worked fine in 7.2, but I doubt it'll be useful to try to figure out just what made that happen. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 16 21:20:38 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 16 Jun 2017 21:20:38 -0000 Subject: [GHC] #13804: MonoLocalBinds/RankNTypes type inference regression in GHC 8.2 In-Reply-To: <050.b9855b85679e008576846333f1b379f9@haskell.org> References: <050.b9855b85679e008576846333f1b379f9@haskell.org> Message-ID: <065.7471b66a5eabfa5bd38388624aff4f23@haskell.org> #13804: MonoLocalBinds/RankNTypes type inference regression in GHC 8.2 -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: highest | Milestone: Component: Compiler (Type | Version: 8.2.1-rc2 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: #11698 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Simon Peyton Jones ): In [changeset:"dc8e6861dc5586a8222484afc3bd26c432e2d69c/ghc" dc8e6861/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="dc8e6861dc5586a8222484afc3bd26c432e2d69c" Fix the treatment of 'closed' definitions The IdBindingInfo field of ATcId serves two purposes - to control generalisation when we have -XMonoLocalBinds - to check for floatability when dealing with (static e) These are related, but not the same, and they'd becomme confused. Trac #13804 showed this up via an example like this: f periph = let sr :: forall a. [a] -> [a] sr = if periph then reverse else id sr2 = sr -- The question: is sr2 generalised? -- It should be, because sr has a type sig -- even though it has periph free in (sr2 [True], sr2 "c") Here sr2 should be generalised, despite the free var 'periph' in 'sr' because 'sr' has a closed type signature. I documented all this very carefully this time, in TcRnTypes: Note [Meaning of IdBindingInfo] Note [Bindings with closed types: ClosedTypeId] }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 16 21:23:25 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 16 Jun 2017 21:23:25 -0000 Subject: [GHC] #13804: MonoLocalBinds/RankNTypes type inference regression in GHC 8.2 In-Reply-To: <050.b9855b85679e008576846333f1b379f9@haskell.org> References: <050.b9855b85679e008576846333f1b379f9@haskell.org> Message-ID: <065.92ce72c795019d5ce5b05b3fd153b960@haskell.org> #13804: MonoLocalBinds/RankNTypes type inference regression in GHC 8.2 -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: merge Priority: highest | Milestone: Component: Compiler (Type | Version: 8.2.1-rc2 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: #11698 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * status: new => merge Comment: It took me a surprisingly long time to really understand what's going on here, but I hope that the new documentation will help for next time! Probably merge. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 16 22:41:54 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 16 Jun 2017 22:41:54 -0000 Subject: [GHC] #13804: MonoLocalBinds/RankNTypes type inference regression in GHC 8.2 In-Reply-To: <050.b9855b85679e008576846333f1b379f9@haskell.org> References: <050.b9855b85679e008576846333f1b379f9@haskell.org> Message-ID: <065.e79f3728c10113d9b013141407982a47@haskell.org> #13804: MonoLocalBinds/RankNTypes type inference regression in GHC 8.2 -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: closed Priority: highest | Milestone: 8.2.1 Component: Compiler (Type | Version: 8.2.1-rc2 checker) | Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: #11698 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: merge => closed * resolution: => fixed * milestone: => 8.2.1 Comment: Merged with 15af7156087dec6b1031406bcbe4508b71cc3470. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 16 23:43:34 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 16 Jun 2017 23:43:34 -0000 Subject: [GHC] #13837: Calling qReifyInstances on out-of-scope Name leads to GHC internal error Message-ID: <050.2ec8c837e6eed6426d66e4f53ccb99d0@haskell.org> #13837: Calling qReifyInstances on out-of-scope Name leads to GHC internal error -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Template | Version: 8.0.1 Haskell | Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: Compile-time Unknown/Multiple | crash or panic Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- {{{#!hs {-# LANGUAGE TemplateHaskell #-} module Bug where import Language.Haskell.TH.Lib import Language.Haskell.TH.Syntax test_local_tyfam_expansion :: String test_local_tyfam_expansion = $(do fam_name <- newName "Fam" stringE . show =<< qReifyInstances fam_name []) }}} {{{ $ /opt/ghc/8.2.1/bin/ghci Bug2.hs GHCi, version 8.2.0.20170523: http://www.haskell.org/ghc/ :? for help Loaded GHCi configuration from /home/rgscott/.ghci [1 of 1] Compiling Bug ( Bug2.hs, interpreted ) Bug2.hs:9:5: error: • The exact Name ‘Fam_a4pX’ is not in scope Probable cause: you used a unique Template Haskell name (NameU), perhaps via newName, but did not bind it If that's it, then -ddump-splices might be useful • In the argument of reifyInstances: Fam_0 In the untyped splice: $(do fam_name <- newName "Fam" stringE . show =<< qReifyInstances fam_name []) | 9 | $(do fam_name <- newName "Fam" | ^^^^^^^^^^^^^^^^^^^^^^^^^^^^... Bug2.hs:9:5: error: • GHC internal error: ‘Fam_a4pX’ is not in scope during type checking, but it passed the renamer tcl_env of environment: [] • In the type ‘Fam_a4pX’ In the argument of reifyInstances: Fam_0 In the untyped splice: $(do fam_name <- newName "Fam" stringE . show =<< qReifyInstances fam_name []) | 9 | $(do fam_name <- newName "Fam" | ^^^^^^^^^^^^^^^^^^^^^^^^^^^^... }}} This appears to have started happening in GHC 7.10, since with 7.8, you only get this: {{{ 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. [1 of 1] Compiling Bug ( Bug2.hs, interpreted ) Loading package array-0.5.0.0 ... linking ... done. Loading package deepseq-1.3.0.2 ... linking ... done. Loading package containers-0.5.5.1 ... linking ... done. Loading package pretty-1.1.1.1 ... linking ... done. Loading package template-haskell ... linking ... done. Bug2.hs:9:5: The exact Name ‘Fam_a2gK’ is not in scope Probable cause: you used a unique Template Haskell name (NameU), perhaps via newName, but did not bind it If that's it, then -ddump-splices might be useful In the argument of reifyInstances: Fam_0 In the splice: $(do { fam_name <- newName "Fam"; stringE . show =<< qReifyInstances fam_name [] }) }}} This problem appears to be somewhat specific to `qReifyInstances`, since switching it out with `qReify` does not trigger the internal error: {{{#!hs {-# LANGUAGE TemplateHaskell #-} module Bug where import Language.Haskell.TH.Lib import Language.Haskell.TH.Syntax test_local_tyfam_expansion :: String test_local_tyfam_expansion = $(do fam_name <- newName "Fam" stringE . show =<< qReify fam_name) }}} {{{ GHCi, version 8.2.0.20170523: http://www.haskell.org/ghc/ :? for help Loaded GHCi configuration from /home/rgscott/.ghci [1 of 1] Compiling Bug ( Bug2.hs, interpreted ) Bug2.hs:9:5: error: • The exact Name ‘Fam_a4od’ is not in scope Probable cause: you used a unique Template Haskell name (NameU), perhaps via newName, but did not bind it If that's it, then -ddump-splices might be useful • In the untyped splice: $(do fam_name <- newName "Fam" stringE . show =<< qReify fam_name) | 9 | $(do fam_name <- newName "Fam" | ^^^^^^^^^^^^^^^^^^^^^^^^^^^^... Bug2.hs:9:5: error: • The exact Name ‘Fam_a4od’ is not in scope Probable cause: you used a unique Template Haskell name (NameU), perhaps via newName, but did not bind it If that's it, then -ddump-splices might be useful • In the untyped splice: $(do fam_name <- newName "Fam" stringE . show =<< qReify fam_name) | 9 | $(do fam_name <- newName "Fam" | ^^^^^^^^^^^^^^^^^^^^^^^^^^^^... Bug2.hs:9:5: error: • ‘Fam_a4od’ is not in the type environment at a reify • In the untyped splice: $(do fam_name <- newName "Fam" stringE . show =<< qReify fam_name) | 9 | $(do fam_name <- newName "Fam" | ^^^^^^^^^^^^^^^^^^^^^^^^^^^^... }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 16 23:49:24 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 16 Jun 2017 23:49:24 -0000 Subject: [GHC] #13792: Allow building using distro GCC on Windows In-Reply-To: <044.190a71c9e96d6252e4edbb8309f5384f@haskell.org> References: <044.190a71c9e96d6252e4edbb8309f5384f@haskell.org> Message-ID: <059.8f8dc3a1e293d8c9f206139e2befdd69@haskell.org> #13792: Allow building using distro GCC on Windows -------------------------------------+------------------------------------- Reporter: Phyx- | Owner: Phyx- Type: feature request | Status: patch Priority: normal | Milestone: 8.4.1 Component: Build System | Version: 8.0.1 Resolution: | Keywords: Operating System: Windows | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3637 Wiki Page: | -------------------------------------+------------------------------------- Comment (by Tamar Christina ): In [changeset:"fda094d000cf2c2874a8205c8212cb83b52259ef/ghc" fda094d/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="fda094d000cf2c2874a8205c8212cb83b52259ef" Provide way to build using existing C compiler on Windows. Summary: There are various distros that build GHC using their own C compilers such as MSYS2. Currently they have to patch the build scripts everytime. This patch provides the configure argument `--enable-distro-toolchain` which allows one to build using any C compiler on the path. This is also useful for testing new versions of GCC. Test Plan: ./configure --enable-distro-toolchain && make - && make THREADS=9 test ./validate Reviewers: austin, hvr, bgamari Reviewed By: bgamari Subscribers: rwbarton, thomie, erikd, #ghc_windows_task_force GHC Trac Issues: #13792 Differential Revision: https://phabricator.haskell.org/D3637 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 16 23:55:59 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 16 Jun 2017 23:55:59 -0000 Subject: [GHC] #13792: Allow building using distro GCC on Windows In-Reply-To: <044.190a71c9e96d6252e4edbb8309f5384f@haskell.org> References: <044.190a71c9e96d6252e4edbb8309f5384f@haskell.org> Message-ID: <059.7bffb5ab98776bdf82c9371485f9fa39@haskell.org> #13792: Allow building using distro GCC on Windows -------------------------------------+------------------------------------- Reporter: Phyx- | Owner: Phyx- Type: feature request | Status: merge Priority: normal | Milestone: 8.4.1 Component: Build System | Version: 8.0.1 Resolution: | Keywords: Operating System: Windows | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3637 Wiki Page: | -------------------------------------+------------------------------------- Changes (by Phyx-): * status: patch => merge -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 16 23:56:12 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 16 Jun 2017 23:56:12 -0000 Subject: [GHC] #13792: Allow building using distro GCC on Windows In-Reply-To: <044.190a71c9e96d6252e4edbb8309f5384f@haskell.org> References: <044.190a71c9e96d6252e4edbb8309f5384f@haskell.org> Message-ID: <059.3edd844f9603b9f16ee73ad6569fea65@haskell.org> #13792: Allow building using distro GCC on Windows -------------------------------------+------------------------------------- Reporter: Phyx- | Owner: Phyx- Type: feature request | Status: closed Priority: normal | Milestone: 8.4.1 Component: Build System | Version: 8.0.1 Resolution: fixed | Keywords: Operating System: Windows | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3637 Wiki Page: | -------------------------------------+------------------------------------- Changes (by Phyx-): * status: merge => closed * resolution: => fixed -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jun 17 00:17:14 2017 From: ghc-devs at haskell.org (GHC) Date: Sat, 17 Jun 2017 00:17:14 -0000 Subject: [GHC] #13709: Drop GCC Driver In-Reply-To: <044.530378a7ad6f5c3b791a9c874c84177d@haskell.org> References: <044.530378a7ad6f5c3b791a9c874c84177d@haskell.org> Message-ID: <059.972890503e317a9b9c723417da5a0288@haskell.org> #13709: Drop GCC Driver ---------------------------------+---------------------------------------- Reporter: Phyx- | Owner: Phyx- Type: task | Status: patch Priority: normal | Milestone: 8.4.1 Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Windows | Architecture: Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3592 Wiki Page: | ---------------------------------+---------------------------------------- Comment (by Tamar Christina ): In [changeset:"d6cecde585b0980ed8e0050c5a1d315789fb6356/ghc" d6cecde5/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="d6cecde585b0980ed8e0050c5a1d315789fb6356" Remove the Windows GCC driver. Summary: This patch drops the GCC driver and instead moves the only remaining path that we need to keep for backwards compatibility to the settings file. It also generalizes the code that expands `$TopDir` so it can expand it within any location in the string and also changes it so `$TopDir` is expanded only after the words call because `$TopDir` can contains spaces which would be horribly broken. Test Plan: ./validate Reviewers: austin, hvr, bgamari Reviewed By: bgamari Subscribers: rwbarton, thomie, erikd GHC Trac Issues: #13709 Differential Revision: https://phabricator.haskell.org/D3592 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jun 17 00:18:58 2017 From: ghc-devs at haskell.org (GHC) Date: Sat, 17 Jun 2017 00:18:58 -0000 Subject: [GHC] #13709: Drop GCC Driver In-Reply-To: <044.530378a7ad6f5c3b791a9c874c84177d@haskell.org> References: <044.530378a7ad6f5c3b791a9c874c84177d@haskell.org> Message-ID: <059.8596552908d345ce7f9cec8cf779face@haskell.org> #13709: Drop GCC Driver ---------------------------------+---------------------------------------- Reporter: Phyx- | Owner: Phyx- Type: task | Status: closed Priority: normal | Milestone: 8.4.1 Component: Compiler | Version: 8.0.1 Resolution: fixed | Keywords: Operating System: Windows | Architecture: Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3592 Wiki Page: | ---------------------------------+---------------------------------------- Changes (by Phyx-): * status: patch => closed * resolution: => fixed -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jun 17 00:59:40 2017 From: ghc-devs at haskell.org (GHC) Date: Sat, 17 Jun 2017 00:59:40 -0000 Subject: [GHC] #13838: -Wdeferred-type-errors; ghc: panic!; VoidRep; ((() -> ()) :: *) ~# (IO Any :: *) Message-ID: <044.5150fbc131040d8653d1692d9b8b36a2@haskell.org> #13838: -Wdeferred-type-errors; ghc: panic!; VoidRep; ((() -> ()) :: *) ~# (IO Any :: *) -------------------------------------+------------------------------------- Reporter: harry | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: Compile-time Unknown/Multiple | crash or panic Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- My Compiler told me to report this so here you go: {{{ [1 of 1] Compiling Main ( ghc_bug.hs, interpreted ) ghc_bug.hs:3:1: warning: [-Wdeferred-type-errors] * Couldn't match expected type `IO t0' with actual type `() -> ()' * Probable cause: `main' is applied to too few arguments In the expression: main When checking the type of the IO action `main' ghc_bug.hs:3:8: warning: [-Wdeferred-type-errors] * Couldn't match expected type `() -> () -> ()' with actual type `()' * The function `()' is applied to one argument, but its type `()' has none In the expression: () () In an equation for `main': main = () () ghc: panic! (the 'impossible' happened) (GHC version 8.0.1 for x86_64-unknown-linux): corePrepPgm [False] cobox_r1a0 = typeError @ 'VoidRep @ ((() -> ()) :: *) ~# (IO Any :: *) "ghc_bug.hs:3:1: error:\n\ \ * Couldn't match expected type `IO t0' with actual type `() -> ()'\n\ \ * Probable cause: `main' is applied to too few arguments\n\ \ In the expression: main\n\ \ When checking the type of the IO action `main'\n\ \(deferred type error)"# Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug }}} {{{#!hs main :: () -> () main = () () }}} which that in "ghc_bug.hs" "ghc ghc_bug.hs -fdefer-type-errors -dcore-lint -v" gives me the following: {{{ Glasgow Haskell Compiler, Version 8.0.1, stage 2 booted by GHC version 7.10.3 Using binary package database: /usr/lib/ghc-8.0.1/package.conf.d/package.cache Using binary package database: /home/harry/.ghc/x86_64-linux-8.0.1/package.conf.d/package.cache loading package database /usr/lib/ghc-8.0.1/package.conf.d loading package database /home/harry/.ghc/x86_64-linux-8.0.1/package.conf.d wired-in package ghc-prim mapped to ghc-prim-0.5.0.0 wired-in package integer-gmp mapped to integer-gmp-1.0.0.1 wired-in package base mapped to base-4.9.0.0 wired-in package rts mapped to rts wired-in package template-haskell mapped to template-haskell-2.11.0.0 wired-in package ghc mapped to ghc-8.0.1 wired-in package dph-seq not found. wired-in package dph-par not found. Hsc static flags: loading package database /usr/lib/ghc-8.0.1/package.conf.d loading package database /home/harry/.ghc/x86_64-linux-8.0.1/package.conf.d wired-in package ghc-prim mapped to ghc-prim-0.5.0.0 wired-in package integer-gmp mapped to integer-gmp-1.0.0.1 wired-in package base mapped to base-4.9.0.0 wired-in package rts mapped to rts-1.0 wired-in package template-haskell mapped to template-haskell-2.11.0.0 wired-in package ghc mapped to ghc-8.0.1 wired-in package dph-seq not found. wired-in package dph-par not found. *** Chasing dependencies: Chasing modules from: *ghc_bug.hs !!! Chasing dependencies: finished in 0.42 milliseconds, allocated 0.211 megabytes Stable obj: [] Stable BCO: [] Ready for upsweep [NONREC ModSummary { ms_hs_date = ****-**-** **:**:**.********** *** ms_mod = Main, ms_textual_imps = [(Nothing, Prelude)] ms_srcimps = [] }] *** Deleting temp files: Deleting: compile: input file ghc_bug.hs *** Checking old interface for Main: [1 of 1] Compiling Main ( ghc_bug.hs, ghc_bug.o ) *** Parser [Main]: !!! Parser [Main]: finished in 0.14 milliseconds, allocated 0.089 megabytes *** Renamer/typechecker [Main]: !!! Renamer/typechecker [Main]: finished in 28.70 milliseconds, allocated 14.769 megabytes *** Desugar [Main]: Result size of Desugar (after optimization) = {terms: 19, types: 52, coercions: 4} *** Core Linted result of Desugar (after optimization): *** Core Lint errors : in result of Desugar (after optimization) *** : warning: [RHS of cobox_aOD :: ((() -> ()) :: *) ~# (IO Any :: *)] The type of this binder is primitive: cobox_aOD Binder's type: ((() -> ()) :: *) ~# (IO Any :: *) *** Offending Program *** main :: () -> () [LclIdX, Str=DmdType] main = case typeError @ 'VoidRep @ (() :: *) ~# ((() -> () -> ()) :: *) "ghc_bug.hs:2:8: error:\n\ \ * Couldn't match expected type `() -> () -> ()'\n\ \ with actual type `()'\n\ \ * The function `()' is applied to one argument,\n\ \ but its type `()' has none\n\ \ In the expression: () ()\n\ \ In an equation for `main': main = () ()\n\ \(deferred type error)"# of cobox_aOE { __DEFAULT -> (() `cast` (Sub cobox_aOE :: (() :: *) ~R# ((() -> () -> ()) :: *))) () } $trModule :: Module [LclIdX, Str=DmdType] $trModule = Module (TrNameS "main"#) (TrNameS "Main"#) cobox_aOD :: ((() -> ()) :: *) ~# (IO Any :: *) [LclId[CoVarId], Str=DmdType] cobox_aOD = typeError @ 'VoidRep @ ((() -> ()) :: *) ~# (IO Any :: *) "ghc_bug.hs:2:1: error:\n\ \ * Couldn't match expected type `IO t0' with actual type `() -> ()'\n\ \ * Probable cause: `main' is applied to too few arguments\n\ \ In the expression: main\n\ \ When checking the type of the IO action `main'\n\ \(deferred type error)"# main :: IO Any [LclIdX, Str=DmdType] main = runMainIO @ Any (main `cast` (Sub cobox_aOD :: ((() -> ()) :: *) ~R# (IO Any :: *))) *** End of Offense *** : error: Compilation had errors *** Deleting temp files: Deleting: *** Deleting temp dirs: Deleting: }}} and gcc version is: gcc version 7.1.1 20170516 (GCC) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jun 17 01:06:42 2017 From: ghc-devs at haskell.org (GHC) Date: Sat, 17 Jun 2017 01:06:42 -0000 Subject: [GHC] #13836: Some event log events won't be flushed if capability count decreased with setNumCapabitilies In-Reply-To: <046.e07128837fcde826a9a245793a21e443@haskell.org> References: <046.e07128837fcde826a9a245793a21e443@haskell.org> Message-ID: <061.c511aebf4b3abceed1e33f6a7e18344c@haskell.org> #13836: Some event log events won't be flushed if capability count decreased with setNumCapabitilies -------------------------------------+------------------------------------- Reporter: bgamari | Owner: (none) Type: bug | Status: patch Priority: normal | Milestone: Component: Runtime System | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3654 Wiki Page: | -------------------------------------+------------------------------------- Comment (by duog): I'm probably missing something, but by my reading of setNumCapabilities in Shedule.c, n_capabilities can never decrease. If the number of capabilities decreases, enabled_capabilities is used to disable capabiltities. If that is true, then I don't think this can ever happen? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jun 17 01:28:49 2017 From: ghc-devs at haskell.org (GHC) Date: Sat, 17 Jun 2017 01:28:49 -0000 Subject: [GHC] #13836: Some event log events won't be flushed if capability count decreased with setNumCapabitilies In-Reply-To: <046.e07128837fcde826a9a245793a21e443@haskell.org> References: <046.e07128837fcde826a9a245793a21e443@haskell.org> Message-ID: <061.d08d1bf24c1d9cfc3b2b017a93adaadb@haskell.org> #13836: Some event log events won't be flushed if capability count decreased with setNumCapabitilies -------------------------------------+------------------------------------- Reporter: bgamari | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: Component: Runtime System | Version: 8.0.1 Resolution: invalid | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3654 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: patch => closed * resolution: => invalid Comment: Nope, you aren't missing anything at all. I didn't look too carefully at `setNumCapabilities`; it looks like you are right! Good catch. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jun 17 01:50:11 2017 From: ghc-devs at haskell.org (GHC) Date: Sat, 17 Jun 2017 01:50:11 -0000 Subject: [GHC] #13830: '+RTS -s' gives incorrect value for work balance in some cases In-Reply-To: <043.14e010bc8c8133d891369e32e6e80a21@haskell.org> References: <043.14e010bc8c8133d891369e32e6e80a21@haskell.org> Message-ID: <058.b5117b06ab9f14133d9e08c40c7a814f@haskell.org> #13830: '+RTS -s' gives incorrect value for work balance in some cases -------------------------------------+------------------------------------- Reporter: duog | Owner: duog Type: bug | Status: new Priority: normal | Milestone: Component: Runtime System | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Debugging | Unknown/Multiple information is incorrect | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by duog): * owner: (none) => duog Comment: The number of garbage collection threads is limited to the number of cores right? I believe that this bug will result in the work balance being significantly under reported if the number of capabilities is much more than the number of gc threads. I don't expect dynamically changing capabilities is very common in the wild, but a number of capabilities several times the number of cores may be, I think I remember a blog post of Simon Marlow's saying that they do that at facebook. I'm assigning this to myself as I have a fix in mind: track a value like (or instead of) cumulative_par_max_copied_bytes. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jun 17 02:02:57 2017 From: ghc-devs at haskell.org (GHC) Date: Sat, 17 Jun 2017 02:02:57 -0000 Subject: [GHC] #13838: -Wdeferred-type-errors; ghc: panic!; VoidRep; ((() -> ()) :: *) ~# (IO Any :: *) In-Reply-To: <044.5150fbc131040d8653d1692d9b8b36a2@haskell.org> References: <044.5150fbc131040d8653d1692d9b8b36a2@haskell.org> Message-ID: <059.30a74edd71000e23d8fe387bd0cf2033@haskell.org> #13838: -Wdeferred-type-errors; ghc: panic!; VoidRep; ((() -> ()) :: *) ~# (IO Any :: *) -------------------------------------+------------------------------------- Reporter: harry | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): Thanks for the bug report. Interestingly, this program no longer panics with just `-fdefer-type- errors` on GHC 8.2.1 or HEAD: {{{ $ /opt/ghc/8.2.1/bin/ghc Bug.hs -fdefer-type-errors [1 of 1] Compiling Main ( Bug.hs, Bug.o ) Bug.hs:2:1: warning: [-Wdeferred-type-errors] • Couldn't match expected type ‘IO t0’ with actual type ‘() -> ()’ • Probable cause: ‘main’ is applied to too few arguments In the expression: main When checking the type of the IO action ‘main’ | 2 | main = () () | ^ Bug.hs:2:8: warning: [-Wdeferred-type-errors] • Couldn't match expected type ‘() -> () -> ()’ with actual type ‘()’ • The function ‘()’ is applied to one argument, but its type ‘()’ has none In the expression: () () In an equation for ‘main’: main = () () | 2 | main = () () | ^^^^^ Linking Bug ... }}} (It also appears to be `-dcore-lint`-safe.) However, the output isn't exactly what I'd expect from a type-incorrect program that was compiled with `-fdefer-type-errors`: {{{ $ ./Bug Bug: main thread exited (uncaught exception) }}} I would have expected something like this: {{{ $ ./Bug Bug: Bug.hs:2:1: error: • Couldn't match expected type ‘IO t0’ with actual type ‘() -> ()’ • Probable cause: ‘main’ is applied to too few arguments In the expression: main When checking the type of the IO action ‘main’ Bug: Bug.hs:2:8: error: • Couldn't match expected type ‘() -> () -> ()’ with actual type ‘()’ • The function ‘()’ is applied to one argument, but its type ‘()’ has none In the expression: () () In an equation for ‘main’: main = () () }}} I'll investigate which commit fixed the panic. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jun 17 03:35:05 2017 From: ghc-devs at haskell.org (GHC) Date: Sat, 17 Jun 2017 03:35:05 -0000 Subject: [GHC] #13838: -Wdeferred-type-errors; ghc: panic!; VoidRep; ((() -> ()) :: *) ~# (IO Any :: *) In-Reply-To: <044.5150fbc131040d8653d1692d9b8b36a2@haskell.org> References: <044.5150fbc131040d8653d1692d9b8b36a2@haskell.org> Message-ID: <059.475dc9811724079e4913e0e51ea5663a@haskell.org> #13838: -Wdeferred-type-errors; ghc: panic!; VoidRep; ((() -> ()) :: *) ~# (IO Any :: *) -------------------------------------+------------------------------------- Reporter: harry | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: #13292 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * related: => #13292 Comment: Ah, this was fixed in 3c62b1d6b672e7727ea5fa56c69bf43e43d0fd8f (Gather constraints locally in checkMain), the fix for #13292. However, the test program from that commit also suffers from the strange output observed in comment:1. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jun 17 08:09:28 2017 From: ghc-devs at haskell.org (GHC) Date: Sat, 17 Jun 2017 08:09:28 -0000 Subject: [GHC] #13839: GHC warnings do not respect the default module header Message-ID: <048.8053658e99a6145e8d5d5532fd36189f@haskell.org> #13839: GHC warnings do not respect the default module header -------------------------------------+------------------------------------- Reporter: Feuerbach | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- If I compile this program with `-Wall`, I get no warnings: {{{#!hs type T = Int main :: IO () main = return () }}} If I add a module header: {{{#!hs module Main(main) where type T = Int main :: IO () main = return () }}} I now get a warning: {{{ ghcbug2.hs:3:1: warning: [-Wunused-top-binds] Defined but not used: type constructor or class ‘T’ }}} Yet, according to Haskell2010 (section 5.1): > An abbreviated form of module, consisting only of the module body, is permitted. If this is used, the header is assumed to be ‘module Main(main) where’. Therefore, the right behaviour should be to print a warning in the first case as well. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jun 17 10:10:31 2017 From: ghc-devs at haskell.org (GHC) Date: Sat, 17 Jun 2017 10:10:31 -0000 Subject: [GHC] #13840: Pattern matching duplicated record fields Message-ID: <045.fdef3b9f3fabf4bc20ed635197c88b12@haskell.org> #13840: Pattern matching duplicated record fields -------------------------------------+------------------------------------- Reporter: lapdot | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.2 Keywords: | Operating System: Linux Architecture: x86_64 | Type of failure: Compile-time (amd64) | crash or panic Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- GHC panic during compiling pattern matching with duplicated record fields. The following is a short example. Main module: {{{#!hs module Lib ( someFunc ) where import F1 import qualified F2 r :: F2.T2 r = F2.T2 { F2.foo = "ok" } someFunc :: IO () someFunc = case r of F2.T2{ foo = a } -> putStrLn a }}} The first submodule: {{{#!hs module F1 ( T1(..) ) where newtype T1 = T1 { foo :: String } }}} The second submodule: {{{#!hs module F2 ( T2(..) ) where newtype T2 = T2 { foo :: String } }}} GHC compiles the modules successfully if uses DuplicateRecordFields. The modules may be not correct without DuplicateRecordFields. But GHC should show an error message other than panic. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jun 17 14:07:08 2017 From: ghc-devs at haskell.org (GHC) Date: Sat, 17 Jun 2017 14:07:08 -0000 Subject: [GHC] #13841: ADOPT pragma for silencing orphan instances warnings per instance Message-ID: <049.5c7de5285a14f8dfadfcf646791f0efd@haskell.org> #13841: ADOPT pragma for silencing orphan instances warnings per instance -------------------------------------+------------------------------------- Reporter: cocreature | Owner: (none) Type: feature | Status: new request | Priority: normal | Milestone: Component: Compiler | Version: 8.3 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- Currently GHC only allows enabling and disabling the warnings about orphan instances on a module level. I’d like to have an ADOPT pragma that allows disabling the warning for specific instance: {{{#!haskell instance {-# ADOPT #-} C Int }}} Apart from disabling the warning about orphan instances for this specific instance, this pragma should have no effect. I already hacked together a [https://github.com/cocreature/ghc/tree/adopt- pragma prototype] and I’m willing to clean that up and submit a diff if other people like this. This does change the surface language but disabling a warning seem too small of an effect for the ghc proposals process (I’m happy to make a proposal if you disagree). -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jun 17 15:06:56 2017 From: ghc-devs at haskell.org (GHC) Date: Sat, 17 Jun 2017 15:06:56 -0000 Subject: [GHC] #13840: Pattern matching duplicated record fields In-Reply-To: <045.fdef3b9f3fabf4bc20ed635197c88b12@haskell.org> References: <045.fdef3b9f3fabf4bc20ed635197c88b12@haskell.org> Message-ID: <060.2d0621acfa900875f059b27245293d22@haskell.org> #13840: Pattern matching duplicated record fields -------------------------------------+------------------------------------- Reporter: lapdot | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 8.0.2 Resolution: duplicate | Keywords: Operating System: Linux | Architecture: x86_64 Type of failure: Compile-time | (amd64) crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: #13644 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * status: new => closed * resolution: => duplicate * related: => #13644 Comment: To be clear, this is the panic you get: {{{ GHCi, version 8.2.0.20170523: http://www.haskell.org/ghc/ :? for help Loaded GHCi configuration from /home/rgscott/.ghci [1 of 3] Compiling F1 ( F1.hs, interpreted ) [2 of 3] Compiling F2 ( F2.hs, interpreted ) [3 of 3] Compiling Lib ( Lib.hs, interpreted ) ghc: panic! (the 'impossible' happened) (GHC version 8.2.0.20170523 for x86_64-unknown-linux): translateConPatVec: lookup }}} Closing as a duplicate of #13644. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jun 17 15:07:39 2017 From: ghc-devs at haskell.org (GHC) Date: Sat, 17 Jun 2017 15:07:39 -0000 Subject: [GHC] #13644: overloaded name used in record pattern matching leads to panic! (the 'impossible' happened) in ghc In-Reply-To: <049.42fb65c94c9d58534f92e7ad520e593b@haskell.org> References: <049.42fb65c94c9d58534f92e7ad520e593b@haskell.org> Message-ID: <064.5565da8e2ce4a7661d2e2d22a1802e57@haskell.org> #13644: overloaded name used in record pattern matching leads to panic! (the 'impossible' happened) in ghc -------------------------------------+------------------------------------- Reporter: pjljvdlaar | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: #13840 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * related: => #13840 Comment: #13840 is another occurrence of this. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jun 17 16:02:45 2017 From: ghc-devs at haskell.org (GHC) Date: Sat, 17 Jun 2017 16:02:45 -0000 Subject: [GHC] #13385: ghci fails to start when -XRebindableSyntax is passed In-Reply-To: <046.49534d46a543f72893ed665a08de1bb0@haskell.org> References: <046.49534d46a543f72893ed665a08de1bb0@haskell.org> Message-ID: <061.4d99e19794d6f3a6b15f3cdf25afa475@haskell.org> #13385: ghci fails to start when -XRebindableSyntax is passed -------------------------------------+------------------------------------- Reporter: mgsloan | Owner: (none) Type: bug | Status: merge Priority: normal | Milestone: 8.2.1 Component: GHCi | Version: 8.0.1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3621 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: closed => merge * milestone: 8.4.1 => 8.2.1 Comment: Michal Konečný has requested on ghc-devs that we merge this for 8.2. Given that it's a pretty trivial change, I'll do so. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jun 17 16:19:44 2017 From: ghc-devs at haskell.org (GHC) Date: Sat, 17 Jun 2017 16:19:44 -0000 Subject: [GHC] #13842: Is this output from :all-types correct Message-ID: <051.cfc7b25689210c717e176ac64aa524ec@haskell.org> #13842: Is this output from :all-types correct -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- Is this the expected outcome of loading {{{#!hs data B = F | T instance Eq B }}} with [https://downloads.haskell.org/~ghc/latest/docs/html/users_guide/ghci.html #ghci-cmd-:set%20+c :set +c] and then running the `:all-types` command? {{{ λ> :all-types /tmp/test.hs:(3,10)-(3,14): GHC.Classes.Eq Main.B /tmp/test.hs:(3,10)-(3,14): (Main.B -> Main.B -> GHC.Types.Bool) -> GHC.Classes.Eq Main.B /tmp/test.hs:(3,10)-(3,14): (Main.B -> Main.B -> GHC.Types.Bool) -> (Main.B -> Main.B -> GHC.Types.Bool) -> GHC.Classes.Eq Main.B /tmp/test.hs:(3,10)-(3,14): Main.B -> Main.B -> GHC.Types.Bool /tmp/test.hs:(3,10)-(3,14): Main.B -> Main.B -> GHC.Types.Bool }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jun 17 16:24:37 2017 From: ghc-devs at haskell.org (GHC) Date: Sat, 17 Jun 2017 16:24:37 -0000 Subject: [GHC] #13842: Is this output from :all-types correct In-Reply-To: <051.cfc7b25689210c717e176ac64aa524ec@haskell.org> References: <051.cfc7b25689210c717e176ac64aa524ec@haskell.org> Message-ID: <066.31fdf7e55442caf8ca29945c92268512@haskell.org> #13842: Is this output from :all-types correct -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- @@ -14,1 +14,1 @@ - λ> :all-types + > :all-types New description: Is this the expected outcome of loading {{{#!hs data B = F | T instance Eq B }}} with [https://downloads.haskell.org/~ghc/latest/docs/html/users_guide/ghci.html #ghci-cmd-:set%20+c :set +c] and then running the `:all-types` command? {{{ > :all-types /tmp/test.hs:(3,10)-(3,14): GHC.Classes.Eq Main.B /tmp/test.hs:(3,10)-(3,14): (Main.B -> Main.B -> GHC.Types.Bool) -> GHC.Classes.Eq Main.B /tmp/test.hs:(3,10)-(3,14): (Main.B -> Main.B -> GHC.Types.Bool) -> (Main.B -> Main.B -> GHC.Types.Bool) -> GHC.Classes.Eq Main.B /tmp/test.hs:(3,10)-(3,14): Main.B -> Main.B -> GHC.Types.Bool /tmp/test.hs:(3,10)-(3,14): Main.B -> Main.B -> GHC.Types.Bool }}} -- Comment (by Iceland_jack): Gives me an `Addr#` {{{ > :all-types /tmp/test.hs:(6,10)-(6,15): Main.A [a] /tmp/test.hs:(6,10)-(6,15): [a] -> Main.A [a] /tmp/test.hs:(6,10)-(6,15): [a] /tmp/test.hs:(6,10)-(6,15): [a] /tmp/test.hs:(6,10)-(6,15): GHC.Prim.Addr# -> [a] /tmp/test.hs:(6,10)-(6,15): GHC.Prim.Addr# }}} from {{{#!hs data List a = Nil | a ::: List a class A a where getA :: a instance A [a] }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jun 17 16:29:01 2017 From: ghc-devs at haskell.org (GHC) Date: Sat, 17 Jun 2017 16:29:01 -0000 Subject: [GHC] #13843: Expand type information collected (:set +c), used by :all-types, :type-at, .. Message-ID: <051.2dbea686323532b08ecf87717bf64bbe@haskell.org> #13843: Expand type information collected (:set +c), used by :all-types, :type-at, .. -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: feature | Status: new request | Priority: normal | Milestone: Component: Compiler | Version: 8.3 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- When [collecting type information https://downloads.haskell.org/~ghc/latest/docs/html/users_guide/ghci.html #ghci-cmd-:set%20+c] (`:set +c`) GHC does not collect type information from type variables in type synonyms {{{#!hs type Endo a = a -> a }}} data types and families {{{#!hs data List a = Nil | a ::: List a }}} fixity declarations {{{#!hs infixr 5 ::: }}} type class declarations {{{#!hs class A a where getA :: a }}} and type families.. probably other things: the feature appeared one GHC version ago so, has this just not been implemented yet? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jun 17 16:29:19 2017 From: ghc-devs at haskell.org (GHC) Date: Sat, 17 Jun 2017 16:29:19 -0000 Subject: [GHC] #13843: Expand type information collected (:set +c), used by :all-types, :type-at, .. In-Reply-To: <051.2dbea686323532b08ecf87717bf64bbe@haskell.org> References: <051.2dbea686323532b08ecf87717bf64bbe@haskell.org> Message-ID: <066.c1f20f701381c71a7400ff35a20225a9@haskell.org> #13843: Expand type information collected (:set +c), used by :all-types, :type-at, .. -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Description changed by Iceland_jack: @@ -1,4 +1,4 @@ - When [collecting type information - https://downloads.haskell.org/~ghc/latest/docs/html/users_guide/ghci.html - #ghci-cmd-:set%20+c] (`:set +c`) GHC does not collect type information - from type variables in type synonyms + When + [https://downloads.haskell.org/~ghc/latest/docs/html/users_guide/ghci.html + #ghci-cmd-:set%20+c collecting type information] (`:set +c`) GHC does not + collect type information from type variables in type synonyms New description: When [https://downloads.haskell.org/~ghc/latest/docs/html/users_guide/ghci.html #ghci-cmd-:set%20+c collecting type information] (`:set +c`) GHC does not collect type information from type variables in type synonyms {{{#!hs type Endo a = a -> a }}} data types and families {{{#!hs data List a = Nil | a ::: List a }}} fixity declarations {{{#!hs infixr 5 ::: }}} type class declarations {{{#!hs class A a where getA :: a }}} and type families.. probably other things: the feature appeared one GHC version ago so, has this just not been implemented yet? -- -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jun 17 16:33:28 2017 From: ghc-devs at haskell.org (GHC) Date: Sat, 17 Jun 2017 16:33:28 -0000 Subject: [GHC] #13844: Surprising behavior with CPP extension Message-ID: <044.323fec287ece7da9f882c4acbda76c83@haskell.org> #13844: Surprising behavior with CPP extension -------------------------------------+------------------------------------- Reporter: deech | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.2 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- The CPP language extension performs macro substitutions in Haskell comments. I see why it does but it seems like eliding the comments before pre-processing would be less surprising. Eg. compiling: {{{#!hs {-# LANGUAGE CPP -#} -- | Some folder foo/bar/* }}} gives the error: {{{ error: unterminated comment -- | Some folder foo/bar/* }}} because the `/*` in the comment is interpreted as starting a C comment. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jun 17 16:49:51 2017 From: ghc-devs at haskell.org (GHC) Date: Sat, 17 Jun 2017 16:49:51 -0000 Subject: [GHC] #13844: Surprising behavior with CPP extension In-Reply-To: <044.323fec287ece7da9f882c4acbda76c83@haskell.org> References: <044.323fec287ece7da9f882c4acbda76c83@haskell.org> Message-ID: <059.4d4504a54f016ac9842e88b6f7a44c1e@haskell.org> #13844: Surprising behavior with CPP extension -------------------------------------+------------------------------------- Reporter: deech | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): Mmm, this is unfortunate. Eliding comments prior to pre-processing is not trivial but could be done. We would need a simple parser which would also produce `#line` pragmas to ensure that line information is correct in the post-CPP parse. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jun 17 17:08:24 2017 From: ghc-devs at haskell.org (GHC) Date: Sat, 17 Jun 2017 17:08:24 -0000 Subject: [GHC] #13845: Runtime linker too eagerly checks for symbol names Message-ID: <050.86cc0f10c3948104df211f0c9ac47a26@haskell.org> #13845: Runtime linker too eagerly checks for symbol names -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Runtime | Version: 8.0.1 System (Linker) | Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- I discovered this bug in https://github.com/haskell- foundation/foundation/issues/326. Take this file: {{{#!hs module Main (main) where foreign import ccall "notAThing" notAThing :: IO () main :: IO () main = putStrLn "Hello, World!" }}} Compiling and running this file works without issue. But if you try to use the runtime linker, things go haywire: {{{ $ C:\Users\RyanGlScott\Software\ghc\inplace\bin\runghc Bug.hs ghc-stage2.exe: ^^ Could not load 'notAThing', dependency unresolved. See top entry above. Bug.hs: ByteCodeLink: can't find label During interactive linking, GHCi couldn't find the following symbol: notAThing This may be due to you not asking GHCi to load extra object files, archives or DLLs needed by your current session. Restart GHCi, specifying the missing library using the -L/path/to/object/dir and -lmissinglibname flags, or simply by naming the relevant files on the GHCi command line. Alternatively, this link failure might indicate a bug in GHCi. If you suspect the latter, please send a bug report to: glasgow-haskell-bugs at haskell.org }}} This isn't just limited to Windows, since the same thing happens on Linux. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Jun 18 18:31:50 2017 From: ghc-devs at haskell.org (GHC) Date: Sun, 18 Jun 2017 18:31:50 -0000 Subject: [GHC] #13813: DeriveFunctor spuriously rejects existential context with type synonym mentioning the last type variable In-Reply-To: <050.a0d22a04ea0fb2e8ffd652ae181c7c5c@haskell.org> References: <050.a0d22a04ea0fb2e8ffd652ae181c7c5c@haskell.org> Message-ID: <065.c4f932d16ae73702d86118ad0fe19d70@haskell.org> #13813: DeriveFunctor spuriously rejects existential context with type synonym mentioning the last type variable -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: patch Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.1 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3635 Wiki Page: | -------------------------------------+------------------------------------- Comment (by Ryan Scott ): In [changeset:"85731000d8b13476ed3c5bde22af610a27fb00f8/ghc" 8573100/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="85731000d8b13476ed3c5bde22af610a27fb00f8" Look through type synonyms in existential contexts when deriving Functor Summary: This amounts to using `exactTyCoVarsOfType` instead of `tyCoVarsOfType` in the right place. I also fixed a similar issue for `-XDatatypeContexts` while I was in town (but couldn't be bothered to add a test for it). Test Plan: make test TEST=T13813 Reviewers: austin, bgamari, simonpj Reviewed By: simonpj Subscribers: simonpj, rwbarton, thomie GHC Trac Issues: #13813 Differential Revision: https://phabricator.haskell.org/D3635 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Jun 18 18:33:01 2017 From: ghc-devs at haskell.org (GHC) Date: Sun, 18 Jun 2017 18:33:01 -0000 Subject: [GHC] #13813: DeriveFunctor spuriously rejects existential context with type synonym mentioning the last type variable In-Reply-To: <050.a0d22a04ea0fb2e8ffd652ae181c7c5c@haskell.org> References: <050.a0d22a04ea0fb2e8ffd652ae181c7c5c@haskell.org> Message-ID: <065.86e50519c9bda64f979f472b70d617b7@haskell.org> #13813: DeriveFunctor spuriously rejects existential context with type synonym mentioning the last type variable -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.4.1 Component: Compiler (Type | Version: 8.0.1 checker) | Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: GHC rejects | Test Case: valid program | deriving/should_compile/T13813 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3635 Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * testcase: => deriving/should_compile/T13813 * status: patch => closed * resolution: => fixed * milestone: => 8.4.1 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Jun 18 22:23:10 2017 From: ghc-devs at haskell.org (GHC) Date: Sun, 18 Jun 2017 22:23:10 -0000 Subject: [GHC] #13827: "What AbsBinds means" is a pretty confusing doc comment In-Reply-To: <046.d6811ad66cde747388ca38ca27c2378f@haskell.org> References: <046.d6811ad66cde747388ca38ca27c2378f@haskell.org> Message-ID: <061.ff1abed71438a385cd59a2b18c4a14be@haskell.org> #13827: "What AbsBinds means" is a pretty confusing doc comment -------------------------------------+------------------------------------- Reporter: literon | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Documentation | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by literon): Thank you, those notes are much more informative. I wonder why the "what AbsBinds means" note got separated from those? Having read the former at least gives some impression about the latter, but there's still too many black spots (BIND, DBIND, seemingly still hanging references to vars). -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 19 00:48:35 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Jun 2017 00:48:35 -0000 Subject: [GHC] #13844: Surprising behavior with CPP extension In-Reply-To: <044.323fec287ece7da9f882c4acbda76c83@haskell.org> References: <044.323fec287ece7da9f882c4acbda76c83@haskell.org> Message-ID: <059.a0e4aabca33c706f8a7814ed41fe589e@haskell.org> #13844: Surprising behavior with CPP extension -------------------------------------+------------------------------------- Reporter: deech | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by pggiarrusso): Docs for cpphs say "Macros are never expanded within Haskell comments": http://projects.haskell.org/cpphs/#diff. Any chance that helps? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 19 05:13:16 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Jun 2017 05:13:16 -0000 Subject: [GHC] #7169: Warning for incomplete record field label used as function In-Reply-To: <047.31629c8fe32b813e38c132e8d4305995@haskell.org> References: <047.31629c8fe32b813e38c132e8d4305995@haskell.org> Message-ID: <062.cdd2052d474612384f5f94701b24e29d@haskell.org> #7169: Warning for incomplete record field label used as function -------------------------------------+------------------------------------- Reporter: goldfire | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.7 Resolution: | Keywords: Warnings, | newcomer Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by nakaji_dayo): > It would be great if GHC could produce a warning if I use quux as a function somewhere in my code Do you think should be warn at when **using quux** ? \\ I thought it might be necessary when defining `quux`. {{{ data Foo = Bar { frob :: Int } | Baz { frob :: Int, quux :: Bool } -- maybe here f :: Foo -> Bool f x = quux x -- here? }}} Because, I think simply, `quux` function is `quux (Baz _ x) = x` then it is non-exhaustive and should be warned. And, if it in "when use", is this warning done recursively? {{{ data Foo = ... f = quux g = f -- warn here also? }}} I'm sorry if I was wrong. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 19 05:43:01 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Jun 2017 05:43:01 -0000 Subject: [GHC] #13841: ADOPT pragma for silencing orphan instances warnings per instance In-Reply-To: <049.5c7de5285a14f8dfadfcf646791f0efd@haskell.org> References: <049.5c7de5285a14f8dfadfcf646791f0efd@haskell.org> Message-ID: <064.3d1cc012c1dc423c1e1cdd76bdcc2935@haskell.org> #13841: ADOPT pragma for silencing orphan instances warnings per instance -------------------------------------+------------------------------------- Reporter: cocreature | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): That would be OK by me. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 19 06:57:04 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Jun 2017 06:57:04 -0000 Subject: [GHC] #13846: GHC Panic: Visible type application + function type @(_ -> _) Message-ID: <051.8ab26367e3bcc1a9cdc8519f583e39ff@haskell.org> #13846: GHC Panic: Visible type application + function type @(_ -> _) -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.3 Keywords: | Operating System: Unknown/Multiple TypeApplications | Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- {{{ $ ghci -XTypeApplications -ignore-dot-ghci GHCi, version 8.3.20170605: http://www.haskell.org/ghc/ :? for help Prelude> :t fmap @(_ -> _) ghc: panic! (the 'impossible' happened) (GHC version 8.3.20170605 for x86_64-unknown-linux): repSplitAppTys w0_a1pF[tau:2] w0_a1pH[tau:2] [] Call stack: CallStack (from HasCallStack): prettyCurrentCallStack, called at compiler/utils/Outputable.hs:1133:58 in ghc:Outputable callStackDoc, called at compiler/utils/Outputable.hs:1137:37 in ghc:Outputable pprPanic, called at compiler/types/Type.hs:809:9 in ghc:Type Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug Prelude> }}} Doesn't happen with other types it seems, probably something to do with levity polymorphism. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 19 07:37:00 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Jun 2017 07:37:00 -0000 Subject: [GHC] #13830: '+RTS -s' gives incorrect value for work balance in some cases In-Reply-To: <043.14e010bc8c8133d891369e32e6e80a21@haskell.org> References: <043.14e010bc8c8133d891369e32e6e80a21@haskell.org> Message-ID: <058.da5e33063d07bd8429cb1bc3abc3a137@haskell.org> #13830: '+RTS -s' gives incorrect value for work balance in some cases -------------------------------------+------------------------------------- Reporter: duog | Owner: duog Type: bug | Status: patch Priority: normal | Milestone: Component: Runtime System | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Debugging | Unknown/Multiple information is incorrect | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:3658 Wiki Page: | -------------------------------------+------------------------------------- Changes (by duog): * status: new => patch * differential: => Phab:3658 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 19 09:10:20 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Jun 2017 09:10:20 -0000 Subject: [GHC] #13835: ghci with ":set +t" should print type before starting evaluation In-Reply-To: <049.babc2baa39ced2b9a895aa8b0723cb93@haskell.org> References: <049.babc2baa39ced2b9a895aa8b0723cb93@haskell.org> Message-ID: <064.cc49dfc6a66b4ca46912375f4ce78ad9@haskell.org> #13835: ghci with ":set +t" should print type before starting evaluation -------------------------------------+------------------------------------- Reporter: j.waldmann | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: Component: GHCi | Version: Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by j.waldmann): Yes, that's a work-around. But it requires more typing, and the invention of an extra name. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 19 09:24:37 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Jun 2017 09:24:37 -0000 Subject: [GHC] #13847: record construction accepts local unqualified name instead of qualified imported name Message-ID: <049.a967f3782f78e925a6ef9e3030f47afd@haskell.org> #13847: record construction accepts local unqualified name instead of qualified imported name -------------------------------------+------------------------------------- Reporter: j.waldmann | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: GHC accepts Unknown/Multiple | invalid program Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- Given {{{ module A where data A = A { foo :: () } deriving Show }}} the following code is accepted {{{ module Main where import qualified A foo = "foo" main = print $ A.A { foo = () } }}} albeit with a warning {{{ B.hs:4:16: warning: [-Wmissing-fields] • Fields of ‘A.A’ not initialised: foo }}} Indeed the `foo = ()` is type-checked as if it were `A.foo = ()` but the `foo` field is actually not assigned. Evaluation gives {{{ *Main> main A {foo = *** Exception: B.hs:4:16-31: Missing field in record construction foo }}} The code should be rejected outright? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 19 09:51:26 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Jun 2017 09:51:26 -0000 Subject: [GHC] #13847: record construction accepts local unqualified name instead of qualified imported name In-Reply-To: <049.a967f3782f78e925a6ef9e3030f47afd@haskell.org> References: <049.a967f3782f78e925a6ef9e3030f47afd@haskell.org> Message-ID: <064.89cb9128682705dcaac04d6a8d4ec709@haskell.org> #13847: record construction accepts local unqualified name instead of qualified imported name -------------------------------------+------------------------------------- Reporter: j.waldmann | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC accepts | Unknown/Multiple invalid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by mpickering): This is rejected by 7.10.3, but not by 8.0.2. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 19 10:37:36 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Jun 2017 10:37:36 -0000 Subject: [GHC] #13819: TypeApplications-related GHC panic In-Reply-To: <051.cbfd374163652d5209657cd86d4948f0@haskell.org> References: <051.cbfd374163652d5209657cd86d4948f0@haskell.org> Message-ID: <066.69c6edd3ea1026e9a3c70b8a2ddc47a1@haskell.org> #13819: TypeApplications-related GHC panic -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: bug | Status: new Priority: high | Milestone: 8.2.1 Component: Compiler (Type | Version: 8.2.1-rc2 checker) | Keywords: Resolution: | TypeApplications Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): See also #13846 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 19 10:38:21 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Jun 2017 10:38:21 -0000 Subject: [GHC] #13846: GHC Panic: Visible type application + function type @(_ -> _) In-Reply-To: <051.8ab26367e3bcc1a9cdc8519f583e39ff@haskell.org> References: <051.8ab26367e3bcc1a9cdc8519f583e39ff@haskell.org> Message-ID: <066.d082ac1f656797a662f437772efd69f2@haskell.org> #13846: GHC Panic: Visible type application + function type @(_ -> _) -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.3 Resolution: | Keywords: | TypeApplications Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * cc: goldfire (added) Comment: I'm betting this is a dup of #13819. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 19 10:44:08 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Jun 2017 10:44:08 -0000 Subject: [GHC] #13827: "What AbsBinds means" is a pretty confusing doc comment In-Reply-To: <046.d6811ad66cde747388ca38ca27c2378f@haskell.org> References: <046.d6811ad66cde747388ca38ca27c2378f@haskell.org> Message-ID: <061.0fd2b1fec2ccc7c63b8e70d0146a6867@haskell.org> #13827: "What AbsBinds means" is a pretty confusing doc comment -------------------------------------+------------------------------------- Reporter: literon | Owner: (none) Type: bug | Status: patch Priority: normal | Milestone: Component: Documentation | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3659 Wiki Page: | -------------------------------------+------------------------------------- Changes (by hsyl20): * status: new => patch * differential: => Phab:D3659 Comment: I have tried to infer what was meant (see Phab:D3659). -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 19 10:55:08 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Jun 2017 10:55:08 -0000 Subject: [GHC] #13827: "What AbsBinds means" is a pretty confusing doc comment In-Reply-To: <046.d6811ad66cde747388ca38ca27c2378f@haskell.org> References: <046.d6811ad66cde747388ca38ca27c2378f@haskell.org> Message-ID: <061.cab55c49407e0df2c54c313ad8ca6eca@haskell.org> #13827: "What AbsBinds means" is a pretty confusing doc comment -------------------------------------+------------------------------------- Reporter: literon | Owner: (none) Type: bug | Status: patch Priority: normal | Milestone: Component: Documentation | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3659 Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): Close, thank you.... I wrote up a a better comment on the plane, and will commit when I have a decent internet connection -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 19 11:09:26 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Jun 2017 11:09:26 -0000 Subject: [GHC] #13009: Hierarchical Module Structure for GHC In-Reply-To: <045.859215149771e4346ac45f933feca22e@haskell.org> References: <045.859215149771e4346ac45f933feca22e@haskell.org> Message-ID: <060.9ae7c63034f5d72d5cfee4153d7bfce5@haskell.org> #13009: Hierarchical Module Structure for GHC -------------------------------------+------------------------------------- Reporter: hsyl20 | Owner: hsyl20 Type: task | Status: patch Priority: low | Milestone: Component: GHC API | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3647 Wiki Page: | ModuleDependencies/Hierarchical | -------------------------------------+------------------------------------- Comment (by hsyl20): I have tried Cabal's feature to rename modules (thanks @hvr): https://github.com/hsyl20/ghc-api-compat With a package of this kind, the transition should be smoother for package maintainers. The benefits may seem small because it's only module renaming for now. But it's a preliminary step to help fixing other issues. > but it is already hard to use haddock with GHC as not that many functions have haddock comments and you need to read the Notes in order to understand everything. I would say that we should fix haddock comments in GHC. In addition maybe we could make haddock export Notes in the generated documentation. > Long standing patches and branches need to be re-based and imports renamed. While I appreciate that it's a one time cost, it's a very painful one. Agreed. However it may not be that painful. I've already rebased the patch (e.g., on "Trees that grow" and on the patch introducing the FileCleanup module) and it was easy. > the split between ghc/ghci and compiler/GHC.Interactive seems weird. It's just the split between ghc-the-program and ghc-the-library. (I have generated some graphs: http://hsyl20.fr/ghc_module_deps/). -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 19 12:12:29 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Jun 2017 12:12:29 -0000 Subject: [GHC] #13009: Hierarchical Module Structure for GHC In-Reply-To: <045.859215149771e4346ac45f933feca22e@haskell.org> References: <045.859215149771e4346ac45f933feca22e@haskell.org> Message-ID: <060.eb4595dbe9efe74990fb3bece2e16694@haskell.org> #13009: Hierarchical Module Structure for GHC -------------------------------------+------------------------------------- Reporter: hsyl20 | Owner: hsyl20 Type: task | Status: patch Priority: low | Milestone: Component: GHC API | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3647 Wiki Page: | ModuleDependencies/Hierarchical | -------------------------------------+------------------------------------- Comment (by bgamari): >> but it is already hard to use haddock with GHC as not that many functions have haddock comments and you need to read the Notes in order to understand everything. > > I would say that we should fix haddock comments in GHC. In addition maybe we could make haddock export Notes in the generated documentation. I agree that we should fix GHC's use of Haddock comments. We've been saying for a long time that all new exported functions should have Haddock comments. We are much better about this than we used to be but there is still a long ways to go > (I have generated some graphs: ​http://hsyl20.fr/ghc_module_deps/). Neat! -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 19 12:15:59 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Jun 2017 12:15:59 -0000 Subject: [GHC] #13832: No parameter-validation in Control.Concurrent.setNumCapabilities In-Reply-To: <051.3d60dff1f88e30b72e07c48763136ae0@haskell.org> References: <051.3d60dff1f88e30b72e07c48763136ae0@haskell.org> Message-ID: <066.5333b79ac3e49ef9707ba95f9a07f79c@haskell.org> #13832: No parameter-validation in Control.Concurrent.setNumCapabilities -------------------------------------+------------------------------------- Reporter: AlistairWard | Owner: (none) Type: bug | Status: closed Priority: low | Milestone: 8.2.1 Component: Core Libraries | Version: 8.0.1 Resolution: fixed | Keywords: | setNumCapabilities Operating System: Linux | Architecture: x86 Type of failure: Runtime crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"b9f9670c8cf4eac8798a8cb3e683d0411f9e94ec/ghc" b9f9670/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="b9f9670c8cf4eac8798a8cb3e683d0411f9e94ec" rts: Ensure that new capability count is > 0 The Haskell wrapper already checks this but we should also check it in the RTS to catch non-Haskell callers. See #13832. }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 19 12:15:59 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Jun 2017 12:15:59 -0000 Subject: [GHC] #13822: GHC not using injectivity? In-Reply-To: <051.2a3d251c10227c1a71de0d444bf548f8@haskell.org> References: <051.2a3d251c10227c1a71de0d444bf548f8@haskell.org> Message-ID: <066.0b0b1b0026ad2ace016af1d99f8030e1@haskell.org> #13822: GHC not using injectivity? -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.2.1 Component: Compiler | Version: 8.0.1 Resolution: fixed | Keywords: | InjectiveFamilies, TypeInType Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | typecheck/should_compile/T13822 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"04ca0360a6b38627c2608ed7468f4d8c46257e3a/ghc" 04ca036/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="04ca0360a6b38627c2608ed7468f4d8c46257e3a" testsuite: Add testcase for #13822 Reviewers: austin Subscribers: rwbarton, thomie GHC Trac Issues: #13822 Differential Revision: https://phabricator.haskell.org/D3655 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 19 12:15:59 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Jun 2017 12:15:59 -0000 Subject: [GHC] #13821: bindings for unlifted types are allowed in .hs-boot files and .hsig files In-Reply-To: <043.23e5a07809642797cc00f131ea2af984@haskell.org> References: <043.23e5a07809642797cc00f131ea2af984@haskell.org> Message-ID: <058.0878e816d3c1d2a1a2a13b027dba24fe@haskell.org> #13821: bindings for unlifted types are allowed in .hs-boot files and .hsig files -------------------------------------+------------------------------------- Reporter: duog | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.1-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: GHC accepts | Test Case: invalid program | typecheck/should_fail/T13821 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"271e0f087b6560f445d7e6bd7f6cecec917e1085/ghc" 271e0f0/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="271e0f087b6560f445d7e6bd7f6cecec917e1085" Add test cases for #13821 Reviewers: austin, bgamari Reviewed By: bgamari Subscribers: rwbarton, thomie GHC Trac Issues: #13821 Differential Revision: https://phabricator.haskell.org/D3642 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 19 12:15:59 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Jun 2017 12:15:59 -0000 Subject: [GHC] #13812: deriveConstants: no objdump program given (OpenBSD) In-Reply-To: <045.636d394562a9f1cf977240b7a6005dbd@haskell.org> References: <045.636d394562a9f1cf977240b7a6005dbd@haskell.org> Message-ID: <060.0c0d4b3618d099cef3bd6c199a252b5c@haskell.org> #13812: deriveConstants: no objdump program given (OpenBSD) -------------------------------------+------------------------------------- Reporter: roland | Owner: (none) Type: bug | Status: patch Priority: normal | Milestone: Component: Build System | Version: Resolution: | Keywords: Operating System: OpenBSD | Architecture: Type of failure: Building GHC | Unknown/Multiple failed | Test Case: Blocked By: | Blocking: Related Tickets: #9549 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"a9b62a3e883e536724602bce2a5bb8a21eba02cc/ghc" a9b62a3/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="a9b62a3e883e536724602bce2a5bb8a21eba02cc" configure: Look for objdump on OpenBSD and AIX deriveConstants requires objdump for both of these operating systems, in addition to Windows. See #13812. Test Plan: Validate on OpenBSD and AIX Reviewers: hvr, austin Reviewed By: hvr Subscribers: rwbarton, thomie, erikd GHC Trac Issues: #13812 Differential Revision: https://phabricator.haskell.org/D3638 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 19 12:15:59 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Jun 2017 12:15:59 -0000 Subject: [GHC] #7198: New codegen more than doubles compile time of T3294 In-Reply-To: <047.96b5f0effd7d95ff044f855e6d48f3db@haskell.org> References: <047.96b5f0effd7d95ff044f855e6d48f3db@haskell.org> Message-ID: <062.9953c47d987f4628b3139af3a772d8b5@haskell.org> #7198: New codegen more than doubles compile time of T3294 -------------------------------------+------------------------------------- Reporter: simonmar | Owner: simonmar Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.4.2 (CodeGen) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: #4258 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"6a2264d2bd47e993c43a592bd614ab7917184e22/ghc" 6a2264d/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="6a2264d2bd47e993c43a592bd614ab7917184e22" cmm/CmmLayoutStack: avoid generating unnecessary reloads This tries to be more precise when generating reloads of local registers in proc points. Previously we'd reload all local registers that were live. But we used liveness information that assumed local registers survive native calls. For the purpose of reloading registers this is an overapproximation and might lead to generating huge amounts of unnecessary reloads (in case there's another proc point before the register is used). This change takes the approach of moving the generation of reloads to a second pass over the Cmm, which allows to recompute the liveness and can use the knowledge that local registers do *not* survive calls. This leads to generating only useful reloads. For an extreme example where this helps a lot please see T3294. This should also fix #7198 Finally, this re-introduces the code to do Cmm rewriting using in `Dataflow` module (with the difference that we know operate on a whole block at a time). Signed-off-by: Michal Terepeta Reviewers: austin, bgamari, simonmar Reviewed By: simonmar Subscribers: kavon, rwbarton, thomie GHC Trac Issues: #7198 Differential Revision: https://phabricator.haskell.org/D3586 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 19 13:03:54 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Jun 2017 13:03:54 -0000 Subject: [GHC] #13808: Bump Cabal submodule In-Reply-To: <046.c4d8d53c6ca66b8eb549fabfe34bf347@haskell.org> References: <046.c4d8d53c6ca66b8eb549fabfe34bf347@haskell.org> Message-ID: <061.c7dab35bb298b412a63e67b0b45ddb50@haskell.org> #13808: Bump Cabal submodule -------------------------------------+------------------------------------- Reporter: bgamari | Owner: (none) Type: bug | Status: closed Priority: highest | Milestone: 8.2.1 Component: Compiler | Version: 8.2.1-rc2 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => closed * resolution: => fixed Comment: Done in 1ab05dac3c42d5873b6fdfda84abce56f44c2618. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 19 13:04:26 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Jun 2017 13:04:26 -0000 Subject: [GHC] #13385: ghci fails to start when -XRebindableSyntax is passed In-Reply-To: <046.49534d46a543f72893ed665a08de1bb0@haskell.org> References: <046.49534d46a543f72893ed665a08de1bb0@haskell.org> Message-ID: <061.35d9bbe1b8a7b69011c2560ba9a76a12@haskell.org> #13385: ghci fails to start when -XRebindableSyntax is passed -------------------------------------+------------------------------------- Reporter: mgsloan | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.2.1 Component: GHCi | Version: 8.0.1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3621 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: merge => closed Comment: Merged with c89ef44bbf8c11fca9a12d8fc52c57b382055630. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 19 15:21:03 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Jun 2017 15:21:03 -0000 Subject: [GHC] #13841: ADOPT pragma for silencing orphan instances warnings per instance In-Reply-To: <049.5c7de5285a14f8dfadfcf646791f0efd@haskell.org> References: <049.5c7de5285a14f8dfadfcf646791f0efd@haskell.org> Message-ID: <064.db682d20792e4cb666e736c181d62c98@haskell.org> #13841: ADOPT pragma for silencing orphan instances warnings per instance -------------------------------------+------------------------------------- Reporter: cocreature | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #602, #10150 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * related: => #602, #10150 Comment: (See also #10150, which is essentially the same thing as this ticket.) Let me offer a dissenting opinion. I don't think we should be introducing tailor-made pragmas to suppress certain warnings like this. If we are in the business of suppressing warnings, we really should have a general mechanism that could work for //any// warning by delimiting regions of code that should have the warning disabled (the subject of #602). IMO, anything less than this is asking for trouble down the road. Moreover, I'm not a fan of changing the syntax of instances themselves just for the purposes of warning generation. We already have at least one pragma you can put in the same position, so now this would lead to pragma noise like: {{{#!hs instance {-# OVERLAPPING #-} {-# ADOPT #-} C T }}} In addition, we'd have to update the GHC and Template Haskell ASTs to support this, and I don't think what this buys us is worth the cost. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 19 15:22:08 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Jun 2017 15:22:08 -0000 Subject: [GHC] #10150: Suppress orphan instance warning per instance In-Reply-To: <045.dd025a940793eea395715281eec0b7db@haskell.org> References: <045.dd025a940793eea395715281eec0b7db@haskell.org> Message-ID: <060.d4e1d32ff50c098607abdd19ce7b5fa6@haskell.org> #10150: Suppress orphan instance warning per instance -------------------------------------+------------------------------------- Reporter: ezyang | Owner: (none) Type: feature request | Status: new Priority: low | Milestone: Component: Compiler (Type | Version: 7.11 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: #602, #13841 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * related: => #602, #13841 Comment: See also #13841. As I note in https://ghc.haskell.org/trac/ghc/ticket/13841#comment:2, I think the right way to solve this is to pursue #602. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 19 15:48:29 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Jun 2017 15:48:29 -0000 Subject: [GHC] #13847: record construction accepts local unqualified name instead of qualified imported name In-Reply-To: <049.a967f3782f78e925a6ef9e3030f47afd@haskell.org> References: <049.a967f3782f78e925a6ef9e3030f47afd@haskell.org> Message-ID: <064.ecac4f11dff236a526fe4917cb76c2c9@haskell.org> #13847: record construction accepts local unqualified name instead of qualified imported name -------------------------------------+------------------------------------- Reporter: j.waldmann | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC accepts | Unknown/Multiple invalid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * cc: adamgundry (added) Comment: This regression was introduced in b1884b0e62f62e3c0859515c4137124ab0c9560e (`Implement DuplicateRecordFields`). -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 19 15:51:19 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Jun 2017 15:51:19 -0000 Subject: [GHC] #13844: Surprising behavior with CPP extension In-Reply-To: <044.323fec287ece7da9f882c4acbda76c83@haskell.org> References: <044.323fec287ece7da9f882c4acbda76c83@haskell.org> Message-ID: <059.038a76c508699977690334c4460d721d@haskell.org> #13844: Surprising behavior with CPP extension -------------------------------------+------------------------------------- Reporter: deech | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): `cpphs` works very differently than `cpp` internally, so I'd be surprised if the techniques that `cpphs` are using to accomplish that would be applicable to `cpp`. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 19 15:53:06 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Jun 2017 15:53:06 -0000 Subject: [GHC] #13830: '+RTS -s' gives incorrect value for work balance in some cases In-Reply-To: <043.14e010bc8c8133d891369e32e6e80a21@haskell.org> References: <043.14e010bc8c8133d891369e32e6e80a21@haskell.org> Message-ID: <058.b5cf1e856d237c686b47da5c3f24f20c@haskell.org> #13830: '+RTS -s' gives incorrect value for work balance in some cases -------------------------------------+------------------------------------- Reporter: duog | Owner: duog Type: bug | Status: patch Priority: normal | Milestone: Component: Runtime System | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Debugging | Unknown/Multiple information is incorrect | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3658 Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * differential: Phab:3658 => Phab:D3658 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 19 16:01:09 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Jun 2017 16:01:09 -0000 Subject: [GHC] #7169: Warning for incomplete record field label used as function In-Reply-To: <047.31629c8fe32b813e38c132e8d4305995@haskell.org> References: <047.31629c8fe32b813e38c132e8d4305995@haskell.org> Message-ID: <062.8c327a7048d8a715fba8fc711006339c@haskell.org> #7169: Warning for incomplete record field label used as function -------------------------------------+------------------------------------- Reporter: goldfire | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.7 Resolution: | Keywords: Warnings, | newcomer Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): I agree with nakaji-dayo here. Emitting a warning upon every use of `quux` feels like the wrong design choice. To address goldfire's point above: > We want to be able to have fields such as `quux` that are used only with some (but not all) constructors of a type I agree. I think a reasonable design would be: * Introduce a flag for this purpose (proposal: `-Wpartial-records`) * If the flag is enabled and you define a partial record selector (e.g., `data A = B1 { b :: Int } | B2 { b :: Int, wat :: Char }`, emit a warning of the definition site (and only the definition site). * One can disable this warning by prefixing the partial record selector with an underscore (e.g., `data A = B1 { b :: Int } | B2 { b :: Int, _wat :: Char }`). This should allow you to use the partial record for scenarios where it's handy, but it also gives a visual indication that something is fishy about that function. A separate question is if this flag should be implied by `-Wall`. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 19 16:29:29 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Jun 2017 16:29:29 -0000 Subject: [GHC] #13845: Runtime linker too eagerly checks for symbol names In-Reply-To: <050.86cc0f10c3948104df211f0c9ac47a26@haskell.org> References: <050.86cc0f10c3948104df211f0c9ac47a26@haskell.org> Message-ID: <065.f6316400f949eff9b9d6b06ed27ddfca@haskell.org> #13845: Runtime linker too eagerly checks for symbol names -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Runtime System | Version: 8.0.1 (Linker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): As Phyx- notes, this is actually somewhat expected behavior. The reason this happens in `runghc` and not with compiled code is because interpreted mode loads //all// top-level definitions (even those that are not exported). This is a handy feature to have when tinkering around with code in GHCi, but it does mean that you'll need to load all the symbols being used, which results in the linker error. A "workaround" is to use `runghc` with the `-fobject-code` flag, i.e., `runghc --ghc-arg=-fobject-code Bug.hs`. Of course, this somewhat defeats the purpose of using `runghc` in the first place, but thems the breaks. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 19 18:14:48 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Jun 2017 18:14:48 -0000 Subject: [GHC] #13848: Unexpected order of variable quantification with GADT constructor Message-ID: <050.1bdc037c5d3daf9f53281904769def22@haskell.org> #13848: Unexpected order of variable quantification with GADT constructor -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 (Type checker) | Keywords: | Operating System: Unknown/Multiple TypeApplications | Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- Here's some code: {{{#!hs {-# LANGUAGE DataKinds #-} {-# LANGUAGE ExistentialQuantification #-} {-# LANGUAGE GADTs #-} {-# LANGUAGE KindSignatures #-} {-# LANGUAGE ScopedTypeVariables #-} module Foo where data N = Z | S N data Vec (n :: N) a where VNil :: forall a. Vec Z a VCons :: forall n a. a -> Vec n a -> Vec (S n) a }}} I want to use `TypeApplications` on `VCons`. I tried doing so in GHCi: {{{ GHCi, version 8.2.0.20170523: http://www.haskell.org/ghc/ :? for help Loaded GHCi configuration from /home/rgscott/.ghci [1 of 1] Compiling Foo ( Foo.hs, interpreted ) Ok, modules loaded: Foo. λ> :set -XTypeApplications -XDataKinds λ> :t VCons @Z @Int 1 VNil :1:8: error: • Expected a type, but ‘'Z’ has kind ‘N’ • In the type ‘Z’ In the expression: VCons @Z @Int 1 VNil :1:11: error: • Expected kind ‘N’, but ‘Int’ has kind ‘*’ • In the type ‘Int’ In the expression: VCons @Z @Int 1 VNil :1:17: error: • Couldn't match type ‘'Z’ with ‘Int’ Expected type: Vec Int 'Z Actual type: Vec 'Z 'Z • In the fourth argument of ‘VCons’, namely ‘VNil’ In the expression: VCons @Z @Int 1 VNil }}} Huh? That's strange, I would have expected the first type application to be of kind `N`, and the second to be of kind `*`. But GHC disagrees! {{{ λ> :set -fprint-explicit-foralls λ> :type +v VCons VCons :: forall a (n :: N). a -> Vec n a -> Vec ('S n) a }}} That's downright unintuitive to me, since I explicitly specified the order in which the quantified variables should appear in the type signature for `VCons`. Similarly, if you leave out the `forall`s: {{{#!hs data Vec (n :: N) a where VNil :: Vec Z a VCons :: a -> Vec n a -> Vec (S n) a }}} Then `:type +v` will also report the same quantified variable order for `VCons`. This is perhaps less surprising, since the `n` and `a` in `data Vec (n :: N) a` don't scope over the constructors, so GHC must infer the topological order in which the variables appear in each constructor. But I would certainly not expect GHC to do this if I manually specify the order with `forall`. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 19 18:51:34 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Jun 2017 18:51:34 -0000 Subject: [GHC] #7198: New codegen more than doubles compile time of T3294 In-Reply-To: <047.96b5f0effd7d95ff044f855e6d48f3db@haskell.org> References: <047.96b5f0effd7d95ff044f855e6d48f3db@haskell.org> Message-ID: <062.f157c9c88b83607baa882b7faf71f813@haskell.org> #7198: New codegen more than doubles compile time of T3294 -------------------------------------+------------------------------------- Reporter: simonmar | Owner: simonmar Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.4.2 (CodeGen) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: #4258 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by michalt): The above fix almost halves the allocation when compiling T3294 (we're back to the level from 2012/2013 according `perf/compiler/all.T`), so I was thinking about closing this as fixed. Simon, are you ok with this? (or should we look into something more?) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 19 20:56:53 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Jun 2017 20:56:53 -0000 Subject: [GHC] #12379: WARN pragma gives warning `warning: [-Wdeprecations]' In-Reply-To: <045.155a5978502e79d25fe769eea3d3ec0b@haskell.org> References: <045.155a5978502e79d25fe769eea3d3ec0b@haskell.org> Message-ID: <060.b567a1ec2d6c45f4fe2cbde2a10dc505@haskell.org> #12379: WARN pragma gives warning `warning: [-Wdeprecations]' -------------------------------------+------------------------------------- Reporter: zilinc | Owner: (none) Type: bug | Status: merge Priority: low | Milestone: 8.2.1 Component: Documentation | Version: 8.0.1 Resolution: | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: Type of failure: Documentation | Unknown/Multiple bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => merge * milestone: => 8.2.1 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 19 21:43:32 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Jun 2017 21:43:32 -0000 Subject: [GHC] #13827: "What AbsBinds means" is a pretty confusing doc comment In-Reply-To: <046.d6811ad66cde747388ca38ca27c2378f@haskell.org> References: <046.d6811ad66cde747388ca38ca27c2378f@haskell.org> Message-ID: <061.b23eec45f1b844b83d450655e65e963d@haskell.org> #13827: "What AbsBinds means" is a pretty confusing doc comment -------------------------------------+------------------------------------- Reporter: literon | Owner: (none) Type: bug | Status: patch Priority: normal | Milestone: Component: Documentation | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3659 Wiki Page: | -------------------------------------+------------------------------------- Comment (by Simon Peyton Jones ): In [changeset:"5c93df90a96494229b60bbed0971a4b08c0326a6/ghc" 5c93df90/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="5c93df90a96494229b60bbed0971a4b08c0326a6" Improve comments on AbsBinds See Trac #13827. }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 19 23:30:55 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Jun 2017 23:30:55 -0000 Subject: [GHC] #13848: Unexpected order of variable quantification with GADT constructor In-Reply-To: <050.1bdc037c5d3daf9f53281904769def22@haskell.org> References: <050.1bdc037c5d3daf9f53281904769def22@haskell.org> Message-ID: <065.a7efcaec6e4e00ec9901c26c68bf308b@haskell.org> #13848: Unexpected order of variable quantification with GADT constructor -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.1 checker) | Keywords: Resolution: | TypeApplications Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): Above, I implied that GHC was inferring the topological order for `a` and `n` in the type signature for `VCons` even with an explicit `forall`. I just realized there's more to it after reading `Note [mkGADTVars]`. [http://git.haskell.org/ghc.git/blob/5c93df90a96494229b60bbed0971a4b08c0326a6:/compiler/typecheck/TcTyClsDecls.hs#l1855 The relevant excerpt]: {{{ Note [mkGADTVars] ~~~~~~~~~~~~~~~~~ Running example: data T (k1 :: *) (k2 :: *) (a :: k2) (b :: k2) where MkT :: T x1 * (Proxy (y :: x1), z) z We need the rejigged type to be MkT :: forall (x1 :: *) (k2 :: *) (a :: k2) (b :: k2). forall (y :: x1) (z :: *). (k2 ~ *, a ~ (Proxy x1 y, z), b ~ z) => T x1 k2 a b You might naively expect that z should become a universal tyvar, not an existential. (After all, x1 becomes a universal tyvar.) The problem is that the universal tyvars must have exactly the same kinds as the tyConTyVars. z has kind * while b has kind k2. So we need an existential tyvar and a heterogeneous equality constraint. }}} So what's //really// going on is that GHC is putting all of the universally quantified variables (`a`) before the existentially quantified ones (`n`). Still, I still think that GHC ought to adhere to what the user wrote if they bother to write an explicit `forall`, because otherwise you have to trace out the variable order that GHC happens to infer. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 19 23:53:15 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Jun 2017 23:53:15 -0000 Subject: [GHC] #13848: Unexpected order of variable quantification with GADT constructor In-Reply-To: <050.1bdc037c5d3daf9f53281904769def22@haskell.org> References: <050.1bdc037c5d3daf9f53281904769def22@haskell.org> Message-ID: <065.9cf5165ce37cf56a190e1130769e2584@haskell.org> #13848: Unexpected order of variable quantification with GADT constructor -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.1 checker) | Keywords: Resolution: | TypeApplications Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): The question remains: how could we preserve the order in which the user wrote the `forall`d variables? The assumption that they should be partitioned into separate universal and existential groups is baked pretty deeply into the GHC AST, as `DataCon` has separate `dcUnivTyVars` and `dcExTyVars` fields, and never the twain shall meet. One possible solution is to introduce a `dcOrigTyVars :: Maybe [TyVar]` field, which is `Just` the `forall`d variables (in whatever order the user writes) or `Nothing` otherwise. GHC could then use this information when computing `dataConUserType`, which I believe GHC uses for determining the order in which `TypeApplications` happen. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jun 20 01:27:39 2017 From: ghc-devs at haskell.org (GHC) Date: Tue, 20 Jun 2017 01:27:39 -0000 Subject: [GHC] #13681: Remove deprecated ForceSpecConstr In-Reply-To: <049.c8d6f6a3a96e7a7cae56561f41f485a6@haskell.org> References: <049.c8d6f6a3a96e7a7cae56561f41f485a6@haskell.org> Message-ID: <064.e3820fa427d2e7fd0cac0405de522eb9@haskell.org> #13681: Remove deprecated ForceSpecConstr -------------------------------------+------------------------------------- Reporter: mpickering | Owner: (none) Type: task | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: SpecConstr Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by siddhanathan): So if I understand correctly, we can simply remove `SpecConstrAnnotation` from GHC.Exts since it is deprecated? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jun 20 05:46:46 2017 From: ghc-devs at haskell.org (GHC) Date: Tue, 20 Jun 2017 05:46:46 -0000 Subject: [GHC] #13827: "What AbsBinds means" is a pretty confusing doc comment In-Reply-To: <046.d6811ad66cde747388ca38ca27c2378f@haskell.org> References: <046.d6811ad66cde747388ca38ca27c2378f@haskell.org> Message-ID: <061.c2a7b53637913266ee1fe527918fb65e@haskell.org> #13827: "What AbsBinds means" is a pretty confusing doc comment -------------------------------------+------------------------------------- Reporter: literon | Owner: (none) Type: bug | Status: patch Priority: normal | Milestone: Component: Documentation | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3659 Wiki Page: | -------------------------------------+------------------------------------- Comment (by literon): Looks great, thank you! -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jun 20 08:31:23 2017 From: ghc-devs at haskell.org (GHC) Date: Tue, 20 Jun 2017 08:31:23 -0000 Subject: [GHC] #13681: Remove deprecated ForceSpecConstr In-Reply-To: <049.c8d6f6a3a96e7a7cae56561f41f485a6@haskell.org> References: <049.c8d6f6a3a96e7a7cae56561f41f485a6@haskell.org> Message-ID: <064.1e7198b1be6c7d0019813a9bcf2fa470@haskell.org> #13681: Remove deprecated ForceSpecConstr -------------------------------------+------------------------------------- Reporter: mpickering | Owner: (none) Type: task | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: SpecConstr Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by mpickering): Right but there's also places where it is wired into the compiler which need to be removed. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jun 20 09:03:27 2017 From: ghc-devs at haskell.org (GHC) Date: Tue, 20 Jun 2017 09:03:27 -0000 Subject: [GHC] #13849: Remove Binutils<2.17 hack in X86 codegen Message-ID: <045.c476b6fe29867412d9f9aa4657a999c5@haskell.org> #13849: Remove Binutils<2.17 hack in X86 codegen -------------------------------------+------------------------------------- Reporter: hsyl20 | Owner: (none) Type: task | Status: new Priority: low | Milestone: Component: Compiler | Version: 8.0.1 (CodeGen) | Keywords: | Operating System: Unknown/Multiple Architecture: x86_64 | Type of failure: None/Unknown (amd64) | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- The purpose of this ticket is to keep track of an hack that the X86 code generator uses to support binutils<2.17: nativeGen/X86/CodeGen.hs: > HACK: On x86_64 binutils<2.17 is only able to generate > PC32 relocations, hence we only get 32-bit offsets in > the jump table. As these offsets are always negative > we need to properly sign extend them to 64-bit. This > hack should be removed in conjunction with the hack in > PprMach.hs/pprDataItem once binutils 2.17 is standard. nativeGen/X86/Ppr.hs: > x86_64: binutils can't handle the R_X86_64_PC64 > relocation type, which means we can't do > pc-relative 64-bit addresses. Fortunately we're > assuming the small memory model, in which all such > offsets will fit into 32 bits, so we have to stick > to 32-bit offset fields and modify the RTS > appropriately > See Note [x86-64-relative] in includes/rts/storage/InfoTables.h includes/rts/storage/InfoTables.h > Note [x86-64-relative] > There is a complication on the x86_64 platform, where pointeres are > 64 bits, but the tools don't support 64-bit relative relocations. > However, the default memory model (small) ensures that all symbols > have values in the lower 2Gb of the address space, so offsets all > fit in 32 bits. Hence we can use 32-bit offset fields. > Somewhere between binutils-2.16.1 and binutils-2.16.91.0.6, > support for 64-bit PC-relative relocations was added, so maybe this > hackery can go away sometime. As binutils 2.17 is out since 2011, maybe we could remove this hack now. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jun 20 09:27:56 2017 From: ghc-devs at haskell.org (GHC) Date: Tue, 20 Jun 2017 09:27:56 -0000 Subject: [GHC] #13681: Remove deprecated ForceSpecConstr In-Reply-To: <049.c8d6f6a3a96e7a7cae56561f41f485a6@haskell.org> References: <049.c8d6f6a3a96e7a7cae56561f41f485a6@haskell.org> Message-ID: <064.23397646227b1e36b1606b5db3f816f3@haskell.org> #13681: Remove deprecated ForceSpecConstr -------------------------------------+------------------------------------- Reporter: mpickering | Owner: (none) Type: task | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: SpecConstr Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): I'm all for it, but I'm a bit out of touch... would you like to see which packages on Hackage use `ForceSpecConstr`, if any. If any do, asking the maintainer would be good. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jun 20 09:31:27 2017 From: ghc-devs at haskell.org (GHC) Date: Tue, 20 Jun 2017 09:31:27 -0000 Subject: [GHC] #13850: Incorrect function signature causes the impossible to happen Message-ID: <044.04c7b0346db3591cb78860a68efc729b@haskell.org> #13850: Incorrect function signature causes the impossible to happen -------------------------------------+------------------------------------- Reporter: erikd | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.2.1 Component: Compiler | Version: 8.2.1-rc2 Keywords: | Operating System: Linux Architecture: | Type of failure: Compile-time Unknown/Multiple | crash or panic Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- I made a mistake in my function signature: {{{ > cat wibble.hs ecase :: Either a b -> (a -> c) (b -> c) -> c ecase (Left a) f _ = f a ecase (Right b) _ g = g b > ghci wibble.hs GHCi, version 8.2.0.20170507: http://www.haskell.org/ghc/ :? for help Loaded GHCi configuration from /home/erikd/.ghci [1 of 1] Compiling Main ( wibble.hs, interpreted ) ghc: panic! (the 'impossible' happened) (GHC version 8.2.0.20170507 for x86_64-unknown-linux): repSplitAppTys a_a1pA[sk:1] c_a1pC[sk:1] [] Call stack: CallStack (from HasCallStack): prettyCurrentCallStack, called at compiler/utils/Outputable.hs:1134:58 in ghc:Outputable callStackDoc, called at compiler/utils/Outputable.hs:1138:37 in ghc:Outputable pprPanic, called at compiler/types/Type.hs:808:9 in ghc:Type }}} GHC 8.02 correctly reports an error: {{{ GHCi, version 8.0.2: http://www.haskell.org/ghc/ :? for help Loaded GHCi configuration from /home/erikd/.ghci [1 of 1] Compiling Main ( wibble.hs, interpreted ) wibble.hs:1:24: error: • Expecting one fewer argument to ‘a -> c’ Expected kind ‘* -> *’, but ‘a -> c’ has kind ‘*’ • In the type signature: ecase :: Either a b -> (a -> c) (b -> c) -> c }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jun 20 10:06:37 2017 From: ghc-devs at haskell.org (GHC) Date: Tue, 20 Jun 2017 10:06:37 -0000 Subject: [GHC] #13850: Incorrect function signature causes the impossible to happen In-Reply-To: <044.04c7b0346db3591cb78860a68efc729b@haskell.org> References: <044.04c7b0346db3591cb78860a68efc729b@haskell.org> Message-ID: <059.4d084385953e62ca4414767fe050e479@haskell.org> #13850: Incorrect function signature causes the impossible to happen -------------------------------------+------------------------------------- Reporter: erikd | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.2.1 Component: Compiler | Version: 8.2.1-rc2 Resolution: | Keywords: Operating System: Linux | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by erikd): Just tried with git HEAD and that fails in the same way. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jun 20 11:27:10 2017 From: ghc-devs at haskell.org (GHC) Date: Tue, 20 Jun 2017 11:27:10 -0000 Subject: [GHC] #13851: Change in specialisation(?) behaviour since 8.0.2 causes 6x slowdown Message-ID: <049.12eb233680e8d62e08f397274c91a741@haskell.org> #13851: Change in specialisation(?) behaviour since 8.0.2 causes 6x slowdown -------------------------------------+------------------------------------- Reporter: mpickering | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.1-rc2 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- I was investigating some benchmarks and I noticed some odd results if I duplicated one of my tests. Reproduction: https://github.com/mpickering/probable-eureka Looking at the core, it seems that repeating the definition means that one of the key functions doesn't get specialised as expected which leads to a much slower program. Observe that in the first two benchmarks there is a worker function `go :: Int# -> Int -> ReaderT Int (StateT Int Identity Int` but in the third benchmark this is specialised to `$sgo :: Int# -> Int -> Int -> Int# -> Int# -> Identity (Int, Int)`. Removing the duplicate benchmark means that specialisation happens properly in the first case as well. The proper specialisation also happens in 8.0.2. This causes the first two cases to be 6x slower than the last case. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jun 20 11:59:10 2017 From: ghc-devs at haskell.org (GHC) Date: Tue, 20 Jun 2017 11:59:10 -0000 Subject: [GHC] #13852: Can we have more SIMD primops, corresponding to the untapped AVX etc. instructions? Message-ID: <054.7970fd47b788896732a324aafb5794c0@haskell.org> #13852: Can we have more SIMD primops, corresponding to the untapped AVX etc. instructions? -------------------------------------+------------------------------------- Reporter: | Owner: (none) leftaroundabout | Type: feature | Status: new request | Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 (LLVM) | Keywords: | Operating System: Unknown/Multiple Architecture: x86_64 | Type of failure: None/Unknown (amd64) | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- [http://hackage.haskell.org/package/ghc-prim-0.5.0.0/docs/GHC- Prim.html#g:28 GHC.Prim] contains a good couple of vectorised instructions, which can be [http://hackage.haskell.org/package/primitive- simd-0.1.0.0/docs/Data-Primitive-SIMD.html used by libraries] for generating nice fast e.g. sums of floating-point vectors. However, several instructions that modern processors could vectorise are missing there. In particular, I would like to be able to use the VPSLLVD...VPSRAVD shifting operations, and at some point perhaps VPMAXSQ...VPMINUQ maximum/minimum operations. It would be great if corresponding primops could be added. Else I would like to know – where is this stuff even defined? [http://hackage.haskell.org/package/ghc- prim-0.5.0.0/docs/src/GHC.Prim.html GHC.Prim] as such seems to be merely an automatically-generated dummy module, mostly for Haddock. (On the other hand, I find it also a bit strange that there are primops for [http://hackage.haskell.org/package/ghc-prim-0.5.0.0/docs/GHC- Prim.html#v:quotInt8X16-35- integer division], which is apparently [https://stackoverflow.com/questions/16822757/sse-integer-division not supported by SSE/AVX] at all!) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jun 20 12:41:22 2017 From: ghc-devs at haskell.org (GHC) Date: Tue, 20 Jun 2017 12:41:22 -0000 Subject: [GHC] #13851: Change in specialisation(?) behaviour since 8.0.2 causes 6x slowdown In-Reply-To: <049.12eb233680e8d62e08f397274c91a741@haskell.org> References: <049.12eb233680e8d62e08f397274c91a741@haskell.org> Message-ID: <064.a4c6dd9ae5de001ecdf41dccc133d0f8@haskell.org> #13851: Change in specialisation(?) behaviour since 8.0.2 causes 6x slowdown -------------------------------------+------------------------------------- Reporter: mpickering | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.1-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by mpickering): pacak could reproduce this as well, here is the difference in numbers. http://lpaste.net/356380 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jun 20 13:10:07 2017 From: ghc-devs at haskell.org (GHC) Date: Tue, 20 Jun 2017 13:10:07 -0000 Subject: [GHC] #13852: Can we have more SIMD primops, corresponding to the untapped AVX etc. instructions? In-Reply-To: <054.7970fd47b788896732a324aafb5794c0@haskell.org> References: <054.7970fd47b788896732a324aafb5794c0@haskell.org> Message-ID: <069.5c0ceaec50fcef1fd9ffc1653142842d@haskell.org> #13852: Can we have more SIMD primops, corresponding to the untapped AVX etc. instructions? -------------------------------------+------------------------------------- Reporter: leftaroundabout | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler (LLVM) | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: x86_64 | (amd64) Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): Mayte [wiki:AddingNewPrimitiveOperations] may help? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jun 20 13:10:43 2017 From: ghc-devs at haskell.org (GHC) Date: Tue, 20 Jun 2017 13:10:43 -0000 Subject: [GHC] #13827: "What AbsBinds means" is a pretty confusing doc comment In-Reply-To: <046.d6811ad66cde747388ca38ca27c2378f@haskell.org> References: <046.d6811ad66cde747388ca38ca27c2378f@haskell.org> Message-ID: <061.05e1da01f971f6866caf96d3ea072ce1@haskell.org> #13827: "What AbsBinds means" is a pretty confusing doc comment -------------------------------------+------------------------------------- Reporter: literon | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.2.1 Component: Documentation | Version: 8.0.1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3659 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: patch => closed * resolution: => fixed * milestone: => 8.2.1 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jun 20 13:14:27 2017 From: ghc-devs at haskell.org (GHC) Date: Tue, 20 Jun 2017 13:14:27 -0000 Subject: [GHC] #13009: Hierarchical Module Structure for GHC In-Reply-To: <045.859215149771e4346ac45f933feca22e@haskell.org> References: <045.859215149771e4346ac45f933feca22e@haskell.org> Message-ID: <060.9e3232df7baf6e617580bb41c2d3fcc9@haskell.org> #13009: Hierarchical Module Structure for GHC -------------------------------------+------------------------------------- Reporter: hsyl20 | Owner: hsyl20 Type: task | Status: patch Priority: low | Milestone: Component: GHC API | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3647 Wiki Page: | ModuleDependencies/Hierarchical | -------------------------------------+------------------------------------- Comment (by bgamari): hsyl20, we discussed this in the call yesterday and it seems that we generally agree that this sort of restructuring is something that we want to do. However, we would really like to have a discussion of the concrete restructuring. Currently the best means we have for collaboratively discussing a document like this is the [[https://github.com/ghc-proposals /ghc-proposals|GHC Proposal process]]. Do you think you could write up a proposal giving your proposed restructuring and describing how we plan to mitigate the adverse effects for API users? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jun 20 14:18:40 2017 From: ghc-devs at haskell.org (GHC) Date: Tue, 20 Jun 2017 14:18:40 -0000 Subject: [GHC] #13852: Can we have more SIMD primops, corresponding to the untapped AVX etc. instructions? In-Reply-To: <054.7970fd47b788896732a324aafb5794c0@haskell.org> References: <054.7970fd47b788896732a324aafb5794c0@haskell.org> Message-ID: <069.32b37b5ebbca543cc7c8aa3ac665bf9c@haskell.org> #13852: Can we have more SIMD primops, corresponding to the untapped AVX etc. instructions? -------------------------------------+------------------------------------- Reporter: leftaroundabout | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler (LLVM) | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: x86_64 | (amd64) Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by leftaroundabout): That definitely helps, but I'm still far from understanding what I'd need to do do enable those AVX operations myself. [https://ghc.haskell.org/trac/ghc/wiki/AddingNewPrimitiveOperations The linked Wiki article] doesn't seem to be quite up-to-date WRT [https://github.com/ghc/ghc/blob/master/rts/PrimOps.cmm Primops.cmm], in which I can neither find any hint of any of the vectorised instructions, nor the {{{quotIntegerzh}}} example. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jun 20 14:56:59 2017 From: ghc-devs at haskell.org (GHC) Date: Tue, 20 Jun 2017 14:56:59 -0000 Subject: [GHC] #13810: Gold linker fails In-Reply-To: <045.174b108f34b20d346eba46d31b44114b@haskell.org> References: <045.174b108f34b20d346eba46d31b44114b@haskell.org> Message-ID: <060.de36513fb15b9883ac2a22d84eb1c3b6@haskell.org> #13810: Gold linker fails ---------------------------------+---------------------------------------- Reporter: ksaric | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: linker Operating System: Linux | Architecture: Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | ---------------------------------+---------------------------------------- Changes (by basvandijk): * cc: basvandijk (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jun 20 14:57:01 2017 From: ghc-devs at haskell.org (GHC) Date: Tue, 20 Jun 2017 14:57:01 -0000 Subject: [GHC] #13852: Can we have more SIMD primops, corresponding to the untapped AVX etc. instructions? In-Reply-To: <054.7970fd47b788896732a324aafb5794c0@haskell.org> References: <054.7970fd47b788896732a324aafb5794c0@haskell.org> Message-ID: <069.10ae16574c804a50c52643f8f6add9cd@haskell.org> #13852: Can we have more SIMD primops, corresponding to the untapped AVX etc. instructions? -------------------------------------+------------------------------------- Reporter: leftaroundabout | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler (LLVM) | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: x86_64 | (amd64) Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by hsyl20): Primitive operations on vectors are named `Vec*` in [https://github.com/ghc/ghc/blob/b1fa386cdae1af45fdd3519014be850f83414ab3/compiler/prelude/primops.txt.pp#L2994 prelude/primops.txt.pp] (e.g, `VecDivOp`). The genprimopcode utility generates a primop per vector type and width. For instance in compiler/stage1/build/primop-list.hs-incl: {{{ , (VecDivOp FloatVec 4 W32) , (VecDivOp FloatVec 2 W64) , (VecDivOp FloatVec 8 W32) , (VecDivOp FloatVec 4 W64) , (VecDivOp FloatVec 16 W32) , (VecDivOp FloatVec 8 W64) }}} These are converted from Stg to Cmm by `translateOp` in [https://github.com/ghc/ghc/blob/b1fa386cdae1af45fdd3519014be850f83414ab3/compiler/codeGen/StgCmmPrim.hs#L1245 codeGen/StgCmmPrim.hs]. For instance, `VecDivOp FloatVec` becomes `MO_VF_Quot`. Then you need to use the LLVM backend to convert Cmm into LLVM (textual) IR. This is done by `genMachOp_slow` in [https://github.com/ghc/ghc/blob/b1fa386cdae1af45fdd3519014be850f83414ab3/compiler/llvmGen/LlvmCodeGen/CodeGen.hs#L1367 llvmGen/LlvmCodeGen/CodeGen.hs]. Finally LLVM generates the assembly and GHC [https://github.com/ghc/ghc/blob/b1fa386cdae1af45fdd3519014be850f83414ab3/compiler/llvmGen/LlvmMangler.hs replaces some instructions] because it can't guarantee that the alignment is correct. Note that the native code generator don't support them yet: you have to use the LLVM backend. If the instructions you want are supported by LLVM, they should be relatively easy to add. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jun 20 15:04:00 2017 From: ghc-devs at haskell.org (GHC) Date: Tue, 20 Jun 2017 15:04:00 -0000 Subject: [GHC] #13009: Hierarchical Module Structure for GHC In-Reply-To: <045.859215149771e4346ac45f933feca22e@haskell.org> References: <045.859215149771e4346ac45f933feca22e@haskell.org> Message-ID: <060.800cda1d1a2dcfdc8916a313790aa6d5@haskell.org> #13009: Hierarchical Module Structure for GHC -------------------------------------+------------------------------------- Reporter: hsyl20 | Owner: hsyl20 Type: task | Status: patch Priority: low | Milestone: Component: GHC API | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3647 Wiki Page: | ModuleDependencies/Hierarchical | -------------------------------------+------------------------------------- Comment (by hsyl20): @bgamari Ok I'll write a proposal. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jun 20 15:57:23 2017 From: ghc-devs at haskell.org (GHC) Date: Tue, 20 Jun 2017 15:57:23 -0000 Subject: [GHC] #13846: GHC Panic: Visible type application + function type @(_ -> _) In-Reply-To: <051.8ab26367e3bcc1a9cdc8519f583e39ff@haskell.org> References: <051.8ab26367e3bcc1a9cdc8519f583e39ff@haskell.org> Message-ID: <066.404f75b6976f4c277c4293e3d83dae94@haskell.org> #13846: GHC Panic: Visible type application + function type @(_ -> _) -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 8.3 Resolution: duplicate | Keywords: | TypeApplications Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #13819 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * status: new => closed * resolution: => duplicate * related: => #13819 Comment: Yes, this is absolutely a duplicate of #13819, as this bug surfaced in the same commit (b207b536ded40156f9adb168565ca78e1eef2c74). To consolidate, I'll close this one in favor of #13819. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jun 20 15:58:00 2017 From: ghc-devs at haskell.org (GHC) Date: Tue, 20 Jun 2017 15:58:00 -0000 Subject: [GHC] #13850: Incorrect function signature causes the impossible to happen In-Reply-To: <044.04c7b0346db3591cb78860a68efc729b@haskell.org> References: <044.04c7b0346db3591cb78860a68efc729b@haskell.org> Message-ID: <059.3f9df73be7f67e0693e09d3db23ea972@haskell.org> #13850: Incorrect function signature causes the impossible to happen -------------------------------------+------------------------------------- Reporter: erikd | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.2.1 Component: Compiler | Version: 8.2.1-rc2 Resolution: duplicate | Keywords: Operating System: Linux | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: #13819 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * status: new => closed * resolution: => duplicate * related: => #13819 Comment: This is a duplicate of #13819, so I'll close this in favor of that ticket. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jun 20 15:59:36 2017 From: ghc-devs at haskell.org (GHC) Date: Tue, 20 Jun 2017 15:59:36 -0000 Subject: [GHC] #13819: TypeApplications-related GHC panic In-Reply-To: <051.cbfd374163652d5209657cd86d4948f0@haskell.org> References: <051.cbfd374163652d5209657cd86d4948f0@haskell.org> Message-ID: <066.b5b36e6dd7a6b6fe1f89ede5cb4f7c4e@haskell.org> #13819: TypeApplications-related GHC panic -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: bug | Status: new Priority: high | Milestone: 8.2.1 Component: Compiler (Type | Version: 8.2.1-rc2 checker) | Keywords: Resolution: | TypeApplications Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: #13846, #13850 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * related: => #13846, #13850 Comment: Two more ways to trigger this panic: * #13846: {{{ $ ghci -XTypeApplications -ignore-dot-ghci GHCi, version 8.3.20170605: http://www.haskell.org/ghc/ :? for help Prelude> :t fmap @(_ -> _) ghc: panic! (the 'impossible' happened) (GHC version 8.3.20170605 for x86_64-unknown-linux): repSplitAppTys w0_a1pF[tau:2] w0_a1pH[tau:2] [] Call stack: CallStack (from HasCallStack): prettyCurrentCallStack, called at compiler/utils/Outputable.hs:1133:58 in ghc:Outputable callStackDoc, called at compiler/utils/Outputable.hs:1137:37 in ghc:Outputable pprPanic, called at compiler/types/Type.hs:809:9 in ghc:Type Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug }}} * #13850 {{{ > cat wibble.hs ecase :: Either a b -> (a -> c) (b -> c) -> c ecase (Left a) f _ = f a ecase (Right b) _ g = g b > ghci wibble.hs GHCi, version 8.2.0.20170507: http://www.haskell.org/ghc/ :? for help Loaded GHCi configuration from /home/erikd/.ghci [1 of 1] Compiling Main ( wibble.hs, interpreted ) ghc: panic! (the 'impossible' happened) (GHC version 8.2.0.20170507 for x86_64-unknown-linux): repSplitAppTys a_a1pA[sk:1] c_a1pC[sk:1] [] Call stack: CallStack (from HasCallStack): prettyCurrentCallStack, called at compiler/utils/Outputable.hs:1134:58 in ghc:Outputable callStackDoc, called at compiler/utils/Outputable.hs:1138:37 in ghc:Outputable pprPanic, called at compiler/types/Type.hs:808:9 in ghc:Type }}} Both of these were also caused by b207b536ded40156f9adb168565ca78e1eef2c74. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jun 20 16:13:08 2017 From: ghc-devs at haskell.org (GHC) Date: Tue, 20 Jun 2017 16:13:08 -0000 Subject: [GHC] #13851: Change in specialisation(?) behaviour since 8.0.2 causes 6x slowdown In-Reply-To: <049.12eb233680e8d62e08f397274c91a741@haskell.org> References: <049.12eb233680e8d62e08f397274c91a741@haskell.org> Message-ID: <064.b5ec264175618cbfaa9a37aafe493726@haskell.org> #13851: Change in specialisation(?) behaviour since 8.0.2 causes 6x slowdown -------------------------------------+------------------------------------- Reporter: mpickering | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.1-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): Here's a version with no dependencies: {{{#!hs {-# LANGUAGE BangPatterns #-} {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE FunctionalDependencies #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE UndecidableInstances #-} module Main (main) where -- | Benchmarks for various effect system implementations -- import Criterion.Main import Data.Bits import Data.Int import Data.IORef import Data.Ratio import Data.Time ( getCurrentTime, utctDayTime ) import Control.Exception import Control.Monad import Control.Monad.Trans.Class import qualified Control.Monad.Trans.State.Strict as S import Control.Monad.Trans.Reader import System.CPUTime ( getCPUTime ) import System.IO.Unsafe -- Use only state, lift variable number of effects over/under -------------------------------------------------------------------------------- test1mtl :: MonadState Int m => Int -> m Int test1mtl n = foldM f 1 [0..n] where f acc x | x `rem` 5 == 0 = do s <- get put $! (s + 1) pure $! max acc x | otherwise = pure $! max acc x main = do -- Used to definitively disable bench argument inlining -- !n <- randomRIO (1000000, 1000000) :: IO Int !m <- randomRIO (0, 0) :: IO Int let runRT = (`runReaderT` (m :: Int)) let runS = (`S.runState` (m :: Int)) replicateM_ 100 $ do !n <- randomRIO (1000000, 1000000) :: IO Int evaluate $ (runS . runRT . test1mtl) n replicateM_ 100 $ do !n <- randomRIO (1000000, 1000000) :: IO Int evaluate $ (runS . runRT . test1mtl) n replicateM_ 100 $ do !n <- randomRIO (1000000, 1000000) :: IO Int evaluate $ (runS . runRT . runRT . test1mtl) n ----- -- Auxiliary ---- class Monad m => MonadState s m | m -> s where get :: m s get = state (\s -> (s, s)) put :: s -> m () put s = state (\_ -> ((), s)) state :: (s -> (a, s)) -> m a state f = do s <- get let ~(a, s') = f s put s' return a {-# MINIMAL state | get, put #-} instance MonadState s m => MonadState s (ReaderT r m) where get = lift get put = lift . put state = lift . state instance Monad m => MonadState s (S.StateT s m) where get = S.get put = S.put state = S.state class Random a where randomR :: RandomGen g => (a,a) -> g -> (a,g) -- random :: RandomGen g => g -> (a, g) randomRIO :: (a,a) -> IO a randomRIO range = getStdRandom (randomR range) instance Random Int where randomR = randomIvalIntegral -- ; random = randomBounded randomIvalIntegral :: (RandomGen g, Integral a) => (a, a) -> g -> (a, g) randomIvalIntegral (l,h) = randomIvalInteger (toInteger l, toInteger h) {-# SPECIALIZE randomIvalInteger :: (Num a) => (Integer, Integer) -> StdGen -> (a, StdGen) #-} randomIvalInteger :: (RandomGen g, Num a) => (Integer, Integer) -> g -> (a, g) randomIvalInteger (l,h) rng | l > h = randomIvalInteger (h,l) rng | otherwise = case (f 1 0 rng) of (v, rng') -> (fromInteger (l + v `mod` k), rng') where (genlo, genhi) = genRange rng b = fromIntegral genhi - fromIntegral genlo + 1 q = 1000 k = h - l + 1 magtgt = k * q f mag v g | mag >= magtgt = (v, g) | otherwise = v' `seq`f (mag*b) v' g' where (x,g') = next g v' = (v * b + (fromIntegral x - fromIntegral genlo)) class RandomGen g where next :: g -> (Int, g) genRange :: g -> (Int,Int) genRange _ = (minBound, maxBound) data StdGen = StdGen !Int32 !Int32 instance RandomGen StdGen where next = stdNext genRange _ = stdRange stdRange :: (Int,Int) stdRange = (1, 2147483562) stdNext :: StdGen -> (Int, StdGen) stdNext (StdGen s1 s2) = (fromIntegral z', StdGen s1'' s2'') where z' = if z < 1 then z + 2147483562 else z z = s1'' - s2'' k = s1 `quot` 53668 s1' = 40014 * (s1 - k * 53668) - k * 12211 s1'' = if s1' < 0 then s1' + 2147483563 else s1' k' = s2 `quot` 52774 s2' = 40692 * (s2 - k' * 52774) - k' * 3791 s2'' = if s2' < 0 then s2' + 2147483399 else s2' getStdRandom :: (StdGen -> (a,StdGen)) -> IO a getStdRandom f = atomicModifyIORef' theStdGen (swap . f) where swap (v,g) = (g,v) theStdGen :: IORef StdGen theStdGen = unsafePerformIO $ do rng <- mkStdRNG 0 newIORef rng mkStdRNG :: Integer -> IO StdGen mkStdRNG o = do ct <- getCPUTime (sec, psec) <- getTime return (createStdGen (sec * 12345 + psec + ct + o)) createStdGen :: Integer -> StdGen createStdGen s = mkStdGen32 $ fromIntegral s mkStdGen32 :: Int32 -> StdGen mkStdGen32 sMaybeNegative = StdGen (s1+1) (s2+1) where s = sMaybeNegative .&. maxBound (q, s1) = s `divMod` 2147483562 s2 = q `mod` 2147483398 getTime :: IO (Integer, Integer) getTime = do utc <- getCurrentTime let daytime = toRational $ utctDayTime utc return $ quotRem (numerator daytime) (denominator daytime) }}} {{{ $ /opt/ghc/8.0.2/bin/ghc MultiBench2.hs -O2 -fforce-recomp [1 of 1] Compiling Main ( MultiBench2.hs, MultiBench2.o ) Linking MultiBench2 ... $ time ./MultiBench2 real 0m2.954s user 0m2.952s sys 0m0.000s $ /opt/ghc/8.2.1/bin/ghc MultiBench2.hs -O2 -fforce-recomp [1 of 1] Compiling Main ( MultiBench2.hs, MultiBench2.o ) Linking MultiBench2 ... $ time ./MultiBench2 real 0m12.335s user 0m12.292s sys 0m0.048s }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jun 20 16:32:42 2017 From: ghc-devs at haskell.org (GHC) Date: Tue, 20 Jun 2017 16:32:42 -0000 Subject: [GHC] #13853: TypeApplications and record syntax don't mix Message-ID: <050.02c1b6e1840fb2482585dba240a7dea1@haskell.org> #13853: TypeApplications and record syntax don't mix -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: feature | Status: new request | Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Keywords: | Operating System: Unknown/Multiple TypeApplications | Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- Let's fire up GHCi: {{{ $ ~/Software/ghc-8.2.0.20170507/bin/ghci GHCi, version 8.2.0.20170507: http://www.haskell.org/ghc/ :? for help Loaded GHCi configuration from /Users/rscott/.ghci λ> :set -XTypeApplications -fprint-explicit-foralls λ> import Data.Functor.Identity }}} I can use `TypeApplications` on `Identity` like so: {{{ λ> Identity @Int 42 Identity 42 }}} But not if I try to use record syntax: {{{ λ> Identity @Int { runIdentity = 42 } :4:15: error: parse error on input ‘{’ λ> (Identity @Int) { runIdentity = 42 } :7:1: error: • Couldn't match expected type ‘Identity a0’ with actual type ‘Int -> Identity Int’ • In the expression: (Identity @Int) {runIdentity = 42} In an equation for ‘it’: it = (Identity @Int) {runIdentity = 42} }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jun 20 16:36:47 2017 From: ghc-devs at haskell.org (GHC) Date: Tue, 20 Jun 2017 16:36:47 -0000 Subject: [GHC] #13853: TypeApplications and record syntax don't mix In-Reply-To: <050.02c1b6e1840fb2482585dba240a7dea1@haskell.org> References: <050.02c1b6e1840fb2482585dba240a7dea1@haskell.org> Message-ID: <065.5620adc807530f67b60f7070d71d8e3c@haskell.org> #13853: TypeApplications and record syntax don't mix -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: | TypeApplications Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Description changed by RyanGlScott: @@ -24,7 +24,0 @@ - λ> (Identity @Int) { runIdentity = 42 } - - :7:1: error: - • Couldn't match expected type ‘Identity a0’ - with actual type ‘Int -> Identity Int’ - • In the expression: (Identity @Int) {runIdentity = 42} - In an equation for ‘it’: it = (Identity @Int) {runIdentity = 42} New description: Let's fire up GHCi: {{{ $ ~/Software/ghc-8.2.0.20170507/bin/ghci GHCi, version 8.2.0.20170507: http://www.haskell.org/ghc/ :? for help Loaded GHCi configuration from /Users/rscott/.ghci λ> :set -XTypeApplications -fprint-explicit-foralls λ> import Data.Functor.Identity }}} I can use `TypeApplications` on `Identity` like so: {{{ λ> Identity @Int 42 Identity 42 }}} But not if I try to use record syntax: {{{ λ> Identity @Int { runIdentity = 42 } :4:15: error: parse error on input ‘{’ }}} -- -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jun 20 17:11:53 2017 From: ghc-devs at haskell.org (GHC) Date: Tue, 20 Jun 2017 17:11:53 -0000 Subject: [GHC] #13851: Change in specialisation(?) behaviour since 8.0.2 causes 6x slowdown In-Reply-To: <049.12eb233680e8d62e08f397274c91a741@haskell.org> References: <049.12eb233680e8d62e08f397274c91a741@haskell.org> Message-ID: <064.b681110625f2c6263ceefaf9d272f2c4@haskell.org> #13851: Change in specialisation(?) behaviour since 8.0.2 causes 6x slowdown -------------------------------------+------------------------------------- Reporter: mpickering | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.1-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * cc: simonpj (added) Comment: The bulk of the increase in runtime is due to 2effe18ab51d66474724d38b20e49cc1b8738f60 (The Early Inline Patch): {{{ Commit 55efc9718b520ef354e32c15c4b49cdfecce412f (Combine identical case alternatives in CSE) ----- $ time ./MultiBench2 real 0m2.786s user 0m2.784s sys 0m0.000s Commit 2effe18ab51d66474724d38b20e49cc1b8738f60 (The Early Inline Patch) ----- $ time ./MultiBench2 real 0m11.861s user 0m11.816s sys 0m0.052s }}} (I'm not sure yet what contributes to the other 0.5 seconds in runtime increase.) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jun 20 17:58:30 2017 From: ghc-devs at haskell.org (GHC) Date: Tue, 20 Jun 2017 17:58:30 -0000 Subject: [GHC] #12363: Type application for infix In-Reply-To: <051.833fc99ca846ecc78974bf61eb05e05f@haskell.org> References: <051.833fc99ca846ecc78974bf61eb05e05f@haskell.org> Message-ID: <066.f5b177f604962202206f72b836b3cf4c@haskell.org> #12363: Type application for infix -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: feature request | Status: new Priority: lowest | Milestone: Component: Compiler | Version: 8.0.1 (Parser) | Keywords: Resolution: | TypeApplications Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * cc: RyanGlScott (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jun 20 18:04:36 2017 From: ghc-devs at haskell.org (GHC) Date: Tue, 20 Jun 2017 18:04:36 -0000 Subject: [GHC] #11758: Drop x86_64 binutils <2.17 hack In-Reply-To: <046.4526d91ede8d490bc5daf7dd1af1ee5c@haskell.org> References: <046.4526d91ede8d490bc5daf7dd1af1ee5c@haskell.org> Message-ID: <061.c7b9dcbfea76d01ff51db190b54d80ff@haskell.org> #11758: Drop x86_64 binutils <2.17 hack -------------------------------------+------------------------------------- Reporter: bgamari | Owner: avd Type: task | Status: closed Priority: normal | Milestone: 8.2.1 Component: Compiler (NCG) | Version: 8.0.1-rc2 Resolution: duplicate | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #12433, #2725 | Differential Rev(s): Phab:D2426 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * related: 12433, 2725 => #12433, #2725 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jun 20 18:05:00 2017 From: ghc-devs at haskell.org (GHC) Date: Tue, 20 Jun 2017 18:05:00 -0000 Subject: [GHC] #13849: Remove Binutils<2.17 hack in X86 codegen In-Reply-To: <045.c476b6fe29867412d9f9aa4657a999c5@haskell.org> References: <045.c476b6fe29867412d9f9aa4657a999c5@haskell.org> Message-ID: <060.dd3016f2d73db3979ea6cb33f51fa1f1@haskell.org> #13849: Remove Binutils<2.17 hack in X86 codegen -------------------------------------+------------------------------------- Reporter: hsyl20 | Owner: (none) Type: task | Status: closed Priority: low | Milestone: Component: Compiler | Version: 8.0.1 (CodeGen) | Resolution: duplicate | Keywords: Operating System: Unknown/Multiple | Architecture: x86_64 | (amd64) Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #2725 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => closed * resolution: => duplicate * related: => #2725 Comment: This is a duplicate of #2725. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jun 20 18:07:58 2017 From: ghc-devs at haskell.org (GHC) Date: Tue, 20 Jun 2017 18:07:58 -0000 Subject: [GHC] #13851: Change in specialisation(?) behaviour since 8.0.2 causes 6x slowdown In-Reply-To: <049.12eb233680e8d62e08f397274c91a741@haskell.org> References: <049.12eb233680e8d62e08f397274c91a741@haskell.org> Message-ID: <064.654806d1bd8874c550a24f055a944a8b@haskell.org> #13851: Change in specialisation(?) behaviour since 8.0.2 causes 6x slowdown -------------------------------------+------------------------------------- Reporter: mpickering | Owner: (none) Type: bug | Status: new Priority: high | Milestone: 8.2.1 Component: Compiler | Version: 8.2.1-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * priority: normal => high * failure: None/Unknown => Runtime performance bug * milestone: => 8.2.1 Comment: Given the magnitude of the change I think we should at least understand this before releasing. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jun 20 20:53:08 2017 From: ghc-devs at haskell.org (GHC) Date: Tue, 20 Jun 2017 20:53:08 -0000 Subject: [GHC] #7198: New codegen more than doubles compile time of T3294 In-Reply-To: <047.96b5f0effd7d95ff044f855e6d48f3db@haskell.org> References: <047.96b5f0effd7d95ff044f855e6d48f3db@haskell.org> Message-ID: <062.2f6d243387c202762751063cc6fae558@haskell.org> #7198: New codegen more than doubles compile time of T3294 -------------------------------------+------------------------------------- Reporter: simonmar | Owner: michalt Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.4.2 (CodeGen) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: #4258 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonmar): * owner: simonmar => michalt Comment: Yes let's close it! I'll let you do the honours. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jun 20 21:52:12 2017 From: ghc-devs at haskell.org (GHC) Date: Tue, 20 Jun 2017 21:52:12 -0000 Subject: [GHC] #13854: the 'impossible' happened initTc: unsolved constraints Message-ID: <048.bc4aff160ba4df4253dfd3e4410a82d0@haskell.org> #13854: the 'impossible' happened initTc: unsolved constraints -------------------------------------+------------------------------------- Reporter: bitemyapp | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.2 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: Compile-time Unknown/Multiple | crash or panic Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- {{{ [7 of 7] Compiling Texas.Api.OrderItems ( src/Texas/Api/OrderItems.hs, interpreted ) ghc: panic! (the 'impossible' happened) (GHC version 8.0.2 for x86_64-unknown-linux): initTc: unsolved constraints WC {wc_insol = [W] OrderItemModified_a1mbC :: t_a1mbB[tau:1] (CHoleCan: OrderItemModified) [W] val_a1mbH :: t_a1mbG[tau:1] (CHoleCan: val) [W] runAccountDB_a1md0 :: t_a1mcZ[tau:1] (CHoleCan: runAccountDB) [W] getOrderItemsByOrderId_a1mdb :: t_a1mda[tau:1] (CHoleCan: getOrderItemsByOrderId)} Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug }}} I have what I believe is a repro of this error, albeit slightly different, located here: https://github.com/bitemyapp/panic-repro-initTc-unsolved- constraints {{{ [3 of 3] Compiling Lib ( src/Lib.hs, .stack- work/dist/x86_64-linux/Cabal-1.24.2.0/build/Lib.o ) ghc: panic! (the 'impossible' happened) (GHC version 8.0.2 for x86_64-unknown-linux): initTc: unsolved constraints WC {wc_insol = [W] over_amEW :: t_amEV[tau:1] (CHoleCan: over) [W] ix_amF5 :: t_amF4[tau:1] (CHoleCan: ix)} Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug }}} This is the error I get there. If I learn more in the process of fixing the original code, I'll report it here. This panic occurs w/ GHC and GHCi. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jun 20 21:57:35 2017 From: ghc-devs at haskell.org (GHC) Date: Tue, 20 Jun 2017 21:57:35 -0000 Subject: [GHC] #13819: TypeApplications-related GHC panic In-Reply-To: <051.cbfd374163652d5209657cd86d4948f0@haskell.org> References: <051.cbfd374163652d5209657cd86d4948f0@haskell.org> Message-ID: <066.24cdc494a24f93c6c6519b0562f7fc7d@haskell.org> #13819: TypeApplications-related GHC panic -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: bug | Status: new Priority: high | Milestone: 8.2.1 Component: Compiler (Type | Version: 8.2.1-rc2 checker) | Keywords: Resolution: | TypeApplications Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: #13846, #13850 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by goldfire): My start toward fixing this is at https://github.com/goldfirere/ghc/tree /uo-thing but I'm about to go on holiday. I may have time to finish while traveling, but no guarantees. If someone wants to carry this over the line, I'd be grateful. Otherwise, back in full action on July 5. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jun 21 01:27:43 2017 From: ghc-devs at haskell.org (GHC) Date: Wed, 21 Jun 2017 01:27:43 -0000 Subject: [GHC] #13854: the 'impossible' happened initTc: unsolved constraints In-Reply-To: <048.bc4aff160ba4df4253dfd3e4410a82d0@haskell.org> References: <048.bc4aff160ba4df4253dfd3e4410a82d0@haskell.org> Message-ID: <063.a7d11bd55e353f52d2914407edc6cc6b@haskell.org> #13854: the 'impossible' happened initTc: unsolved constraints -------------------------------------+------------------------------------- Reporter: bitemyapp | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 8.0.2 Resolution: duplicate | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: #13106 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * status: new => closed * resolution: => duplicate * related: => #13106 Comment: Thanks for the bug report. This is a duplicate of #13106, which has been fixed in GHC 8.2. Note that this panic is usually caused by using identifiers that aren't in-scope (in your case, `over` and `ix`) in just the right way. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jun 21 05:24:46 2017 From: ghc-devs at haskell.org (GHC) Date: Wed, 21 Jun 2017 05:24:46 -0000 Subject: [GHC] #8177: Roles for type families In-Reply-To: <046.bd13b30db1cfd3d4628960446a01267b@haskell.org> References: <046.bd13b30db1cfd3d4628960446a01267b@haskell.org> Message-ID: <061.9614c844f7aa954c871c484e397330b2@haskell.org> #8177: Roles for type families -------------------------------------+------------------------------------- Reporter: simonpj | Owner: goldfire Type: bug | Status: new Priority: normal | Milestone: ⊥ Component: Compiler | Version: 7.6.3 Resolution: | Keywords: TypeFamilies Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3662 Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * differential: => Phab:D3662 Comment: I've uploaded a rough attempt at implementing support for roles for closed type families at Phab:D3662, although there are still some bugs to work out (for instance, the program in comment:32 doesn't typecheck yet, unfortunately). -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jun 21 10:33:03 2017 From: ghc-devs at haskell.org (GHC) Date: Wed, 21 Jun 2017 10:33:03 -0000 Subject: [GHC] #13855: Syntactic sugar to write the recursion in GHC Message-ID: <044.4aac734569df8c83745b2d6f55aa7445@haskell.org> #13855: Syntactic sugar to write the recursion in GHC -------------------------------------+------------------------------------- Reporter: vanto | Owner: (none) Type: feature | Status: new request | Priority: normal | Milestone: Component: Compiler | Version: 8.0.2 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- The recursion is defined by two case that are a base case and a recursive case.\\ Instead of writing two functions to describe the recursion, I propose to write a single function that makes both.\\ {{{}}} should be set to tell the compiler how to compile the function.\\ syntaxe : {{{ exp = }}} examples: {{{ fac :: Int -> Int fac n = 0 = 1 n * fac (n-1) }}} {{{ product :: Num a => [a] -> a product (n:ns) = [] = 1 n * product ns }}} {{{ reverse :: [a] -> [a] reverse (x:xs) = [] = [] reverse xs ++ [x] }}} {{{ insert :: Ord a => a -> [a] -> [a] insert x (y:ys) = x [] = [x] | x <= y = x:y:ys | otherwise = y:insert x ys }}} {{{ drop :: Int -> [a] -> [a] drop n (_:xs) = 0 xs = xs; _ [] = [] drop (n-1) xs }}} {{{ fib :: Int -> Int fib n = 0 = 0; 1 = 1 fib (n-2) + fib (n-1) }}} If someone is interested in this, I encourage him to write a proposal. I don't know how to do it. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jun 21 11:49:01 2017 From: ghc-devs at haskell.org (GHC) Date: Wed, 21 Jun 2017 11:49:01 -0000 Subject: [GHC] #13855: Syntactic sugar to write the recursion in GHC In-Reply-To: <044.4aac734569df8c83745b2d6f55aa7445@haskell.org> References: <044.4aac734569df8c83745b2d6f55aa7445@haskell.org> Message-ID: <059.8d65548d3f303b0469b3dfc286fb8696@haskell.org> #13855: Syntactic sugar to write the recursion in GHC -------------------------------------+------------------------------------- Reporter: vanto | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by j.waldmann): Please don't. You want to introduce new syntax for definition of functions? There are very good reasons for what's currently in the Language Standard. In this case: definitions are equations, because we want to do equational reasoning. Your proposal severely obfuscates the equations. I refuse to parse "fib n = 0 = 0". -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jun 21 16:10:22 2017 From: ghc-devs at haskell.org (GHC) Date: Wed, 21 Jun 2017 16:10:22 -0000 Subject: [GHC] #12356: StaticPointers support in GHCi In-Reply-To: <046.4add1b1a872a2608a03a4c2efa3faa77@haskell.org> References: <046.4add1b1a872a2608a03a4c2efa3faa77@haskell.org> Message-ID: <061.7e8d6c7994c254d0345d6731f4194d97@haskell.org> #12356: StaticPointers support in GHCi -------------------------------------+------------------------------------- Reporter: bgamari | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: 8.2.1 Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #12000, #9878 | Differential Rev(s): Phab:D2504, Wiki Page: | Phab:D3663 -------------------------------------+------------------------------------- Changes (by bgamari): * owner: bgamari => (none) * status: closed => new * differential: Phab:D2504 => Phab:D2504, Phab:D3663 * resolution: fixed => Comment: RyanGlScott points out that this patch inadvertently added a `pprTrace` which blurts out in GHCi. Phab:D3663 fixes this. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jun 21 16:13:49 2017 From: ghc-devs at haskell.org (GHC) Date: Wed, 21 Jun 2017 16:13:49 -0000 Subject: [GHC] #13594: Typechecker behavior w.r.t. BangPatterns and nested foralls has changed in 8.2 In-Reply-To: <050.d768cbcd7afd3c7633840a8a13d3da1c@haskell.org> References: <050.d768cbcd7afd3c7633840a8a13d3da1c@haskell.org> Message-ID: <065.b631a4ce7e2f87669e6012d6adea935a@haskell.org> #13594: Typechecker behavior w.r.t. BangPatterns and nested foralls has changed in 8.2 -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: bgamari Type: bug | Status: patch Priority: high | Milestone: 8.2.1 Component: Compiler (Type | Version: 8.2.1-rc2 checker) | Keywords: BangPatterns, Resolution: | RankNTypes Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3661 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => patch * differential: Phab:D3525 => Phab:D3661 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jun 21 16:13:56 2017 From: ghc-devs at haskell.org (GHC) Date: Wed, 21 Jun 2017 16:13:56 -0000 Subject: [GHC] #13841: ADOPT pragma for silencing orphan instances warnings per instance In-Reply-To: <049.5c7de5285a14f8dfadfcf646791f0efd@haskell.org> References: <049.5c7de5285a14f8dfadfcf646791f0efd@haskell.org> Message-ID: <064.4bbf4629176b9ff2238b04f150d1c4c5@haskell.org> #13841: ADOPT pragma for silencing orphan instances warnings per instance -------------------------------------+------------------------------------- Reporter: cocreature | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #602, #10150 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): > If we are in the business of suppressing warnings, we really should have a general mechanism that could work for any warning by delimiting regions of code that should have the warning disabled There is much to be said for that, thank you. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jun 21 16:35:50 2017 From: ghc-devs at haskell.org (GHC) Date: Wed, 21 Jun 2017 16:35:50 -0000 Subject: [GHC] #13856: "Zero-argument" lambda expressions from pretty-print strangely Message-ID: <050.0d7c2840d6bcad243ed441cfec14dd9f@haskell.org> #13856: "Zero-argument" lambda expressions from pretty-print strangely -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Template | Version: 8.0.1 Haskell | Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- An amusing corner case of the language is that you can constructor lambdas with zero arguments using Template Haskell: {{{#!hs {-# LANGUAGE TemplateHaskell #-} import Language.Haskell.TH f :: Int f = $(lamE [] [| 42 |]) }}} But if you try to compile that with `-ddump-splices` on, it'll look quite funny: {{{ $ /opt/ghc/8.2.1/bin/ghci Bug.hs -ddump-splices GHCi, version 8.2.0.20170616: http://www.haskell.org/ghc/ :? for help Loaded GHCi configuration from /home/rgscott/.ghci [1 of 1] Compiling Main ( Bug.hs, interpreted ) Bug.hs:6:7-22: Splicing expression lamE [] [| 42 |] ======> \ -> 42 Ok, modules loaded: Main. }}} Oh dear, `\ -> 42` isn't a valid expression at all. The same thing happens with the Template Haskell pretty-printer: {{{ λ> import Language.Haskell.TH λ> :set -XTemplateHaskell λ> putStrLn $(lamE [] [| 42 |] >>= stringE . pprint) :4:12-48: Splicing expression lamE [] [| 42 |] >>= stringE . pprint ======> "\ -> 42" \ -> 42 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jun 21 17:03:44 2017 From: ghc-devs at haskell.org (GHC) Date: Wed, 21 Jun 2017 17:03:44 -0000 Subject: [GHC] #13856: "Zero-argument" lambda expressions from pretty-print strangely In-Reply-To: <050.0d7c2840d6bcad243ed441cfec14dd9f@haskell.org> References: <050.0d7c2840d6bcad243ed441cfec14dd9f@haskell.org> Message-ID: <065.7926552f6a26ffecf04152842c9c0445@haskell.org> #13856: "Zero-argument" lambda expressions from pretty-print strangely -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: patch Priority: normal | Milestone: Component: Template Haskell | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3664 Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * status: new => patch * differential: => Phab:D3664 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jun 21 17:25:05 2017 From: ghc-devs at haskell.org (GHC) Date: Wed, 21 Jun 2017 17:25:05 -0000 Subject: [GHC] #13857: compactAdd doesn't work with SmallArray# Message-ID: <049.63d32166f598a80d4ab31076e3e7e75b@haskell.org> #13857: compactAdd doesn't work with SmallArray# -------------------------------------+------------------------------------- Reporter: andrewthad | Owner: (none) Type: bug | Status: new Priority: high | Milestone: Component: Runtime | Version: 8.2.1-rc2 System | Keywords: compact | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- I get this when I try to compact a small array: {{{ internal error: stg_compactAddWorkerzh: TODO: SMALL_MUT_ARR_PTRS (GHC version 8.2.0.20170404 for x86_64_unknown_linux) Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug }}} If I look in `rts/Compact.cmm`, I can see that this hasn't been implemented. I haven't seen this in another issue, so I just wanted to make sure it was not overlooked before the 8.2 release. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jun 21 17:30:20 2017 From: ghc-devs at haskell.org (GHC) Date: Wed, 21 Jun 2017 17:30:20 -0000 Subject: [GHC] #7198: New codegen more than doubles compile time of T3294 In-Reply-To: <047.96b5f0effd7d95ff044f855e6d48f3db@haskell.org> References: <047.96b5f0effd7d95ff044f855e6d48f3db@haskell.org> Message-ID: <062.4efa575722e71563f6407b880fcc4019@haskell.org> #7198: New codegen more than doubles compile time of T3294 -------------------------------------+------------------------------------- Reporter: simonmar | Owner: michalt Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 7.4.2 (CodeGen) | Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: #4258 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by michalt): * status: new => closed * resolution: => fixed Comment: Cool, thanks! :) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jun 21 17:42:45 2017 From: ghc-devs at haskell.org (GHC) Date: Wed, 21 Jun 2017 17:42:45 -0000 Subject: [GHC] #13858: Compiling with LaTeX docs on Mint requires additional packages Message-ID: <048.bbb2cdd7a8801a97f3a7c2ccaa9cb421@haskell.org> #13858: Compiling with LaTeX docs on Mint requires additional packages -------------------------------------+------------------------------------- Reporter: HairyDude | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Build System | Version: 8.0.2 Keywords: | Operating System: Linux Architecture: | Type of failure: Building GHC Unknown/Multiple | failed Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- [[Building/Preparation/Linux]] gives a list of optional packages required for building documentation. Having installed these (following the instructions for Debian on Mint 17.1), I tried to build GHC 8.0.2 from source, and compilation stopped with a LaTeX prompt. I hit enter a few times until `make` exited with an error, resulting in the following being the end of `make`'s output. {{{ cd docs/users_guide/build-pdf/users_guide ; xelatex -halt-on-error users_guide.tex This is XeTeX, Version 3.1415926-2.5-0.9999.3 (TeX Live 2013/Debian) restricted \write18 enabled. entering extended mode (./users_guide.tex LaTeX2e <2011/06/27> Babel <3.9h> and hyphenation patterns for 2 languages loaded. (./sphinxmanual.cls Document Class: sphinxmanual 2009/06/02 Document class (Sphinx manual) (/usr/share/texlive/texmf-dist/tex/latex/base/report.cls Document Class: report 2007/10/19 v1.4h Standard LaTeX document class (/usr/share/texlive/texmf-dist/tex/latex/base/size10.clo))) ! LaTeX Error: File `cmap.sty' not found. Type X to quit or to proceed, or enter new name. (Default extension: sty) Enter file name: (/usr/share/texlive/texmf-dist/tex/latex/base/fontenc.sty (/usr/share/texlive/texmf-dist/tex/latex/base/t1enc.def)) (/usr/share/texlive/texmf-dist/tex/generic/babel/babel.sty (/usr/share/texlive/texmf-dist/tex/generic/babel-english/english.ldf (/usr/share/texlive/texmf-dist/tex/generic/babel/babel.def (/usr/share/texlive/texmf-dist/tex/generic/babel/xebabel.def)))) (/usr/share/texlive/texmf-dist/tex/latex/psnfss/times.sty) (./fncychap.sty) (/usr/share/texlive/texmf-dist/tex/latex/tools/longtable.sty) (./sphinx.sty (/usr/share/texlive/texmf-dist/tex/latex/fancyhdr/fancyhdr.sty) (/usr/share/texlive/texmf-dist/tex/latex/base/textcomp.sty (/usr/share/texlive/texmf-dist/tex/latex/base/ts1enc.def)) ! LaTeX Error: File `fancybox.sty' not found. Type X to quit or to proceed, or enter new name. (Default extension: sty) Enter file name: ! LaTeX Error: File `titlesec.sty' not found. Type X to quit or to proceed, or enter new name. (Default extension: sty) Enter file name: (./tabulary.sty (/usr/share/texlive/texmf-dist/tex/latex/tools/array.sty)) (/usr/share/texlive/texmf-dist/tex/latex/amsmath/amsmath.sty For additional information on amsmath, use the `?' option. (/usr/share/texlive/texmf-dist/tex/latex/amsmath/amstext.sty (/usr/share/texlive/texmf-dist/tex/latex/amsmath/amsgen.sty)) (/usr/share/texlive/texmf-dist/tex/latex/amsmath/amsbsy.sty) (/usr/share/texlive/texmf-dist/tex/latex/amsmath/amsopn.sty)) (/usr/share/texlive/texmf-dist/tex/latex/base/makeidx.sty) ! LaTeX Error: File `framed.sty' not found. Type X to quit or to proceed, or enter new name. (Default extension: sty) Enter file name: (/usr/share/texlive/texmf-dist/tex/latex/base/ifthen.sty) (/usr/share/texlive/texmf-dist/tex/latex/graphics/color.sty (/usr/share/texlive/texmf-dist/tex/latex/latexconfig/color.cfg) (/usr/share/texlive/texmf-dist/tex/xelatex/xetex-def/xetex.def)) ! LaTeX Error: File `fancyvrb.sty' not found. Type X to quit or to proceed, or enter new name. (Default extension: sty) Enter file name: ! LaTeX Error: File `threeparttable.sty' not found. Type X to quit or to proceed, or enter new name. (Default extension: sty) Enter file name: ! LaTeX Error: File `footnote.sty' not found. Type X to quit or to proceed, or enter new name. (Default extension: sty) Enter file name: ! Undefined control sequence. \makesavenoteenv l.28 \makesavenoteenv {tabulary} No pages of output. Transcript written on users_guide.log. make[1]: *** [docs/users_guide/users_guide.pdf] Error 1 make: *** [all] Error 2 }}} The missing files are in the packages {{{texlive-latex-recommended}}} and {{{texlive-latex-extra}}}. I've corrected the wiki page but perhaps {{{configure}}} should test for their presence. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jun 21 17:55:03 2017 From: ghc-devs at haskell.org (GHC) Date: Wed, 21 Jun 2017 17:55:03 -0000 Subject: [GHC] #13680: Can't use TypeApplications with empty list expression In-Reply-To: <050.c0d4ac8e4bffb622e3af6a2ccf399ea9@haskell.org> References: <050.c0d4ac8e4bffb622e3af6a2ccf399ea9@haskell.org> Message-ID: <065.ae89a7408e64d779e50bf9e9ccc3f884@haskell.org> #13680: Can't use TypeApplications with empty list expression -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.1 checker) | Keywords: Resolution: | TypeApplications Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): Actually, this limitation applies to more than just empty lists: {{{ $ ~/Software/ghc-8.2.0.20170507/bin/ghci -fprint-explicit-foralls GHCi, version 8.2.0.20170507: http://www.haskell.org/ghc/ :? for help Loaded GHCi configuration from /Users/rscott/.ghci λ> :type +v [1] [1] :: forall {a}. Num a => [a] λ> :type +v [1] @Int :1:5: error: parse error on input ‘@’ }}} So perhaps I was barking up the wrong tree in my investigation in comment:4. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jun 21 17:55:19 2017 From: ghc-devs at haskell.org (GHC) Date: Wed, 21 Jun 2017 17:55:19 -0000 Subject: [GHC] #13680: Can't use TypeApplications with list expressions (was: Can't use TypeApplications with empty list expression) In-Reply-To: <050.c0d4ac8e4bffb622e3af6a2ccf399ea9@haskell.org> References: <050.c0d4ac8e4bffb622e3af6a2ccf399ea9@haskell.org> Message-ID: <065.19973f55112845e3d199d6948044a80b@haskell.org> #13680: Can't use TypeApplications with list expressions -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.1 checker) | Keywords: Resolution: | TypeApplications Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jun 21 18:12:18 2017 From: ghc-devs at haskell.org (GHC) Date: Wed, 21 Jun 2017 18:12:18 -0000 Subject: [GHC] #13825: Allow multiple constructor fields occupy the same word In-Reply-To: <046.a33ec6522f3fa0ad8c7d0d60af2159aa@haskell.org> References: <046.a33ec6522f3fa0ad8c7d0d60af2159aa@haskell.org> Message-ID: <061.73a28e934e1181ea84b822e702acd92b@haskell.org> #13825: Allow multiple constructor fields occupy the same word -------------------------------------+------------------------------------- Reporter: michalt | Owner: michalt Type: bug | Status: new Priority: normal | Milestone: 8.4.1 Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #605 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by michalt): @dfeuer: Thanks for linking #605 - sounds like a much better solution for `Bool` :) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jun 21 18:12:24 2017 From: ghc-devs at haskell.org (GHC) Date: Wed, 21 Jun 2017 18:12:24 -0000 Subject: [GHC] #13859: Bad error message when compacting a Compact# Message-ID: <049.0a8ca29f53f6a9d8119f57074eaae406@haskell.org> #13859: Bad error message when compacting a Compact# -------------------------------------+------------------------------------- Reporter: andrewthad | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.1-rc2 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- When I run this: {{{ main :: IO () main = do cpt@(Compact cpt# _ _) <- compact (55 :: Int) _ <- compactAdd cpt (MyCompact cpt#) return () data MyCompact = MyCompact Compact# }}} I get this error message: {{{ compaction failed: cannot compact mutable objects }}} This error message is misleading. I don't really know if it makes sense to allow a `Compact#` to be stored in a compact region, but if someone tries to do it, I would rather the error say: {{{ cannot compact Compact# values }}} Or something like that. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jun 21 18:14:37 2017 From: ghc-devs at haskell.org (GHC) Date: Wed, 21 Jun 2017 18:14:37 -0000 Subject: [GHC] #13825: Allow multiple constructor fields occupy the same word In-Reply-To: <046.a33ec6522f3fa0ad8c7d0d60af2159aa@haskell.org> References: <046.a33ec6522f3fa0ad8c7d0d60af2159aa@haskell.org> Message-ID: <061.6676547f995e6660f6467df624a3cfdc@haskell.org> #13825: Allow multiple constructor fields occupy the same word -------------------------------------+------------------------------------- Reporter: michalt | Owner: michalt Type: bug | Status: new Priority: normal | Milestone: 8.4.1 Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #605 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Description changed by michalt: @@ -22,3 +22,3 @@ - - Figure out what to do with `Bool` (should it be just `Word8#`? should we - have `Bool#`?) and change its definition (using pattern synonyms for - `True`/`False`) + - ~~Figure out what to do with `Bool` (should it be just `Word8#`? should + we have `Bool#`?) and change its definition (using pattern synonyms for + `True`/`False`)~~ `Bool` should be handled by #605 (see comment:2) New description: The main goal is to reduce the overhead of things like: {{{#!hs data Bloated = Bloated {-# UNPACK #-} !Word8 {-# UNPACK #-} !Int8 {-# UNPACK #-} !Bool }}} Assuming 64-bit architecture, currently those fields will take 8 bytes each! So for this example we'd need: 8 bytes for header + 3 * 8 bytes for fields = 32 bytes. But we should be able to pack the fields into a single word (a word is 8 bytes and each field really only needs 1 byte) for a total of 16 bytes (8 bytes header + 8 bytes for fields, with the 5 bytes being "overhead" due to heap alignment). My understanding is that we need a few things to make this happen: - Ability to refer to fields that are packed into a single word (currently everything in GHC assumes that each field occupies a single word). Simon Marlow started working on this in https://phabricator.haskell.org/D38 - Introduce primitives like `Word8#`, `Int8#`, ... (currently `WordX` and `IntX` are defined as wrappers of `Word#` and `Int#` respectively) and change `WordX`/`IntX` definitions to use those primitives. - ~~Figure out what to do with `Bool` (should it be just `Word8#`? should we have `Bool#`?) and change its definition (using pattern synonyms for `True`/`False`)~~ `Bool` should be handled by #605 (see comment:2) Some additional info: - Thread on ghc-devs: https://mail.haskell.org/pipermail/ghc- devs/2017-June/014304.html -- -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jun 21 20:18:49 2017 From: ghc-devs at haskell.org (GHC) Date: Wed, 21 Jun 2017 20:18:49 -0000 Subject: [GHC] #13859: Bad error message when compacting a Compact# In-Reply-To: <049.0a8ca29f53f6a9d8119f57074eaae406@haskell.org> References: <049.0a8ca29f53f6a9d8119f57074eaae406@haskell.org> Message-ID: <064.e89837f48a2a1de1ae341ca719083baf@haskell.org> #13859: Bad error message when compacting a Compact# -------------------------------------+------------------------------------- Reporter: andrewthad | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.1-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): There are a whole lot of cases to which this objection applies; see `Compact.cmm` around line 120. Perhaps we should just replace the word "mutable" in the error message with the closure type name? It's perhaps a bit more cryptic but less misleading, in general I think it would be nice if we could just make the type checking a bit more precise, turning most of these errors into more comprehensible compile-time errors. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jun 21 20:26:31 2017 From: ghc-devs at haskell.org (GHC) Date: Wed, 21 Jun 2017 20:26:31 -0000 Subject: [GHC] #13860: TODO: SMALL_MUT_ARR_PTRS in Compact.cmm Message-ID: <046.25ac2134055d26c6424aeecbae3f299a@haskell.org> #13860: TODO: SMALL_MUT_ARR_PTRS in Compact.cmm -------------------------------------+------------------------------------- Reporter: bgamari | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.2.1 Component: Compiler | Version: 8.0.1 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- While looking at `Compact.cmm` I noticed that the small mutable array compaction cases are currently TODOs. Presumably this should be addressed. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jun 21 20:36:36 2017 From: ghc-devs at haskell.org (GHC) Date: Wed, 21 Jun 2017 20:36:36 -0000 Subject: [GHC] #13782: Bullish use of Template Haskell's newName causes GHC internal error In-Reply-To: <050.355b0f2ffb6750de858fbc3a1ccc85be@haskell.org> References: <050.355b0f2ffb6750de858fbc3a1ccc85be@haskell.org> Message-ID: <065.cd232c10b9ccf30ab628d16ad81ac9a1@haskell.org> #13782: Bullish use of Template Haskell's newName causes GHC internal error -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: carlostome Type: bug | Status: patch Priority: high | Milestone: 8.2.1 Component: Template Haskell | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: #12503 | Differential Rev(s): Phab:D3641 Wiki Page: | -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"c8370a821bb92ca3846953cb0b37250720087135/ghc" c8370a82/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="c8370a821bb92ca3846953cb0b37250720087135" change filtering of variables in extract_hs_tv_bndrs (fixes #13782) Reviewers: austin, bgamari, goldfire Reviewed By: bgamari Subscribers: rwbarton, thomie GHC Trac Issues: #13782 Differential Revision: https://phabricator.haskell.org/D3641 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jun 21 20:53:59 2017 From: ghc-devs at haskell.org (GHC) Date: Wed, 21 Jun 2017 20:53:59 -0000 Subject: [GHC] #13782: Bullish use of Template Haskell's newName causes GHC internal error In-Reply-To: <050.355b0f2ffb6750de858fbc3a1ccc85be@haskell.org> References: <050.355b0f2ffb6750de858fbc3a1ccc85be@haskell.org> Message-ID: <065.bca2b371534e0343e9b85c5a5a9948b5@haskell.org> #13782: Bullish use of Template Haskell's newName causes GHC internal error -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: carlostome Type: bug | Status: merge Priority: high | Milestone: 8.2.1 Component: Template Haskell | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: #12503 | Differential Rev(s): Phab:D3641 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: patch => merge -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jun 21 20:54:26 2017 From: ghc-devs at haskell.org (GHC) Date: Wed, 21 Jun 2017 20:54:26 -0000 Subject: [GHC] #13859: Bad error message when compacting a Compact# In-Reply-To: <049.0a8ca29f53f6a9d8119f57074eaae406@haskell.org> References: <049.0a8ca29f53f6a9d8119f57074eaae406@haskell.org> Message-ID: <064.f693007fa9e63d8591c2a8c1c218987a@haskell.org> #13859: Bad error message when compacting a Compact# -------------------------------------+------------------------------------- Reporter: andrewthad | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.1-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by andrewthad): Providing the closure type name would help me out a lot. I'm actually now in another situation where I'm getting the "cannot compact mutable objects" message, and it's difficult to track down what it actually is that's causing the problem. Granted, this is only happening because I'm trying to do things that you aren't really supposed to do with compact heap. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jun 21 22:42:07 2017 From: ghc-devs at haskell.org (GHC) Date: Wed, 21 Jun 2017 22:42:07 -0000 Subject: [GHC] #13680: Can't use TypeApplications with [] data constructor (was: Can't use TypeApplications with list expressions) In-Reply-To: <050.c0d4ac8e4bffb622e3af6a2ccf399ea9@haskell.org> References: <050.c0d4ac8e4bffb622e3af6a2ccf399ea9@haskell.org> Message-ID: <065.d8425657865716925b9619a758e63d4a@haskell.org> #13680: Can't use TypeApplications with [] data constructor -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.1 checker) | Keywords: Resolution: | TypeApplications Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): Please ignore what I wrote in comment:5. That is expected behavior, since the type variables for that expression's type would have to be inferred (i.e., invisible). I now suspect the culprit here is `tcExpr`. Specifically, [http://git.haskell.org/ghc.git/blob/76769bdf9e423d89518eae4a5a441ae172c54e96:/compiler/typecheck/TcExpr.hs#l511 this case]: {{{#!hs tcExpr (ExplicitList _ witness exprs) res_ty = case witness of Nothing -> do { res_ty <- expTypeToType res_ty ; (coi, elt_ty) <- matchExpectedListTy res_ty ; exprs' <- mapM (tc_elt elt_ty) exprs ; return $ mkHsWrapCo coi $ ExplicitList elt_ty Nothing exprs' } Just fln -> do { ... } where tc_elt elt_ty expr = tcPolyExpr expr elt_ty }}} Notice that we're calling `matchExpectedListTy` here. This causes the inferred type _not_ to be `forall a. [a]`, but instead something of a coercion type `p[a:tau]`. This means we have to fish out the `a` afterwards, which causes it to have inferred visibility. Blegh. I was hoping that we could just special-case `[]` like so: {{{#!hs tcExpr (ExplicitList _ Nothing []) res_ty = tcCheckId nilDataConName res_ty }}} And while that does achieve what I'd hoped for, it has the unfortunate effect of messing with the pattern-match exhaustivity checker, as the `T12957` test starts failing with this change. So for the time being, I'm out of ideas. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jun 21 23:41:26 2017 From: ghc-devs at haskell.org (GHC) Date: Wed, 21 Jun 2017 23:41:26 -0000 Subject: [GHC] #12119: Can't create injective type family equation with TypeError as the RHS In-Reply-To: <050.21d4af732cea81fafcb58c894bb8137c@haskell.org> References: <050.21d4af732cea81fafcb58c894bb8137c@haskell.org> Message-ID: <065.095bdc1b61453b243e63b914919745c7@haskell.org> #12119: Can't create injective type family equation with TypeError as the RHS -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.1 checker) | Keywords: Resolution: | CustomTypeErrors, TypeFamilies, | InjectiveFamilies Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): Note: this can be implemented in a dead-simple way: {{{#!diff diff --git a/compiler/typecheck/FamInst.hs b/compiler/typecheck/FamInst.hs index cabfb33..b56b68e 100644 --- a/compiler/typecheck/FamInst.hs +++ b/compiler/typecheck/FamInst.hs @@ -42,6 +42,7 @@ import VarSet import Bag( Bag, unionBags, unitBag ) import Control.Monad import NameEnv +import PrelNames import Data.List #include "HsVersions.h" @@ -712,10 +713,13 @@ makeInjectivityErrors fi_ax axiom inj conflicts 2 (vcat (map (pprCoAxBranch fi_ax) eqns)) , coAxBranchSpan (head eqns) ) errorIf p f = if p then [f err_builder axiom] else [] - in errorIf are_conflicts (conflictInjInstErr conflicts ) - ++ errorIf inj_tvs_unused (unusedInjectiveVarsErr unused_inj_tvs) - ++ errorIf tf_headed tfHeadedErr - ++ errorIf wrong_bare_rhs (bareVariableInRHSErr bare_variables) + in case rhs of + TyConApp tc _ + | tyConName tc == errorMessageTypeErrorFamName -> [] + _ -> errorIf are_conflicts (conflictInjInstErr conflicts ) + ++ errorIf inj_tvs_unused (unusedInjectiveVarsErr unused_inj_tvs) + ++ errorIf tf_headed tfHeadedErr + ++ errorIf wrong_bare_rhs (bareVariableInRHSErr bare_variables) }}} Of course, there's still Simon's point about formalizing this idea, which I have yet to do. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jun 22 00:30:22 2017 From: ghc-devs at haskell.org (GHC) Date: Thu, 22 Jun 2017 00:30:22 -0000 Subject: [GHC] #13859: Bad error message when compacting a Compact# In-Reply-To: <049.0a8ca29f53f6a9d8119f57074eaae406@haskell.org> References: <049.0a8ca29f53f6a9d8119f57074eaae406@haskell.org> Message-ID: <064.b4cf13e3a6b74101d05cd55695644e75@haskell.org> #13859: Bad error message when compacting a Compact# -------------------------------------+------------------------------------- Reporter: andrewthad | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.1-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by ezyang): I guess we should actually implement the "Compactable" type class, that will solve this problem once and for all. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jun 22 01:26:29 2017 From: ghc-devs at haskell.org (GHC) Date: Thu, 22 Jun 2017 01:26:29 -0000 Subject: [GHC] #13859: Bad error message when compacting a Compact# In-Reply-To: <049.0a8ca29f53f6a9d8119f57074eaae406@haskell.org> References: <049.0a8ca29f53f6a9d8119f57074eaae406@haskell.org> Message-ID: <064.c932a9c877b6e4d99eb28d08915a47e8@haskell.org> #13859: Bad error message when compacting a Compact# -------------------------------------+------------------------------------- Reporter: andrewthad | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.1-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by andrewthad): The `Compactable` class would be nice for most users, and provided that the instances are generated by GHC (like Typeable and Coercible). Also in my situation, it would still be nice to get a better runtime error since I'm doing dangerous stuff by thawing arrays on the compact heap. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jun 22 02:25:47 2017 From: ghc-devs at haskell.org (GHC) Date: Thu, 22 Jun 2017 02:25:47 -0000 Subject: [GHC] #7169: Warning for incomplete record field label used as function In-Reply-To: <047.31629c8fe32b813e38c132e8d4305995@haskell.org> References: <047.31629c8fe32b813e38c132e8d4305995@haskell.org> Message-ID: <062.c486c18ad15c0844a1c291f004acb504@haskell.org> #7169: Warning for incomplete record field label used as function -------------------------------------+------------------------------------- Reporter: goldfire | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.7 Resolution: | Keywords: Warnings, | newcomer Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by nakaji_dayo): RyanGlScott: Thanks for reply and design.\\ I have additional questions. > Introduce a flag for this purpose (proposal: -Wpartial-records) `-Wpartial-records` may be unnecessary, Because I think It is same meaning to `-Wincomplete-patterns`. > One can disable this warning by prefixing the partial record selector with an underscore (e.g., data A = B1 { b :: Int } | B2 { b :: Int, _wat :: Char }). It seems useful. But, I do not know if it should affect coding style.\\ Is there any existing design that control warnings by function (or variable) name? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jun 22 02:32:22 2017 From: ghc-devs at haskell.org (GHC) Date: Thu, 22 Jun 2017 02:32:22 -0000 Subject: [GHC] #7169: Warning for incomplete record field label used as function In-Reply-To: <047.31629c8fe32b813e38c132e8d4305995@haskell.org> References: <047.31629c8fe32b813e38c132e8d4305995@haskell.org> Message-ID: <062.c3b56bfaf869b9657f05fd6e8dfd0d66@haskell.org> #7169: Warning for incomplete record field label used as function -------------------------------------+------------------------------------- Reporter: goldfire | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.7 Resolution: | Keywords: Warnings, | newcomer Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): > `-Wpartial-records` may be unnecessary, Because I think It is same meaning to `-Wincomplete-patterns`. We could include this warning under the scope of `-Wincomplete-patterns`, but I think it's best to keep these two things separate, since one might conceivably wish to disable partial record warnings while still having `-Wincomplete-patterns` on. > It seems useful. But, I do not know if it should affect coding style. > Is there any existing design that control warnings by function (or variable) name? Yes. The underscore prefix is already an established convention for silencing other warnings. For instance, in the code below, GHC will warn about an unused variable `x` in a pattern match: {{{#!hs f x = 42 }}} But GHC will not warn if you prefix `x` with an underscore: {{{#!hs f _x = 42 }}} Similarly, if you have an unused top-level function, GHC will normally warn about it: {{{#!hs module M (a) where a, b :: Int a = 1 b = 2 }}} But not if it's prefixed with an underscore: {{{#!hs module M (a) where a, _b :: Int a = 1 _b = 2 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jun 22 04:35:35 2017 From: ghc-devs at haskell.org (GHC) Date: Thu, 22 Jun 2017 04:35:35 -0000 Subject: [GHC] #7169: Warning for incomplete record field label used as function In-Reply-To: <047.31629c8fe32b813e38c132e8d4305995@haskell.org> References: <047.31629c8fe32b813e38c132e8d4305995@haskell.org> Message-ID: <062.6e1f34b41f8bbcf42f49fd6fb37cff8c@haskell.org> #7169: Warning for incomplete record field label used as function -------------------------------------+------------------------------------- Reporter: goldfire | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.7 Resolution: | Keywords: Warnings, | newcomer Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by nakaji_dayo): Replying to [comment:19 RyanGlScott]: > We could include this warning under the scope of -Wincomplete-patterns, but I think it's best to keep these two things separate, since one might conceivably wish to disable partial record warnings while still having -Wincomplete-patterns on. I agree. I thought it is safety to separate it. > Yes. The underscore prefix is already an established convention for silencing other warnings. Thanks a lot. I learned.\\ I agree. This rule seems even good in `partial record selector` case. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jun 22 04:36:55 2017 From: ghc-devs at haskell.org (GHC) Date: Thu, 22 Jun 2017 04:36:55 -0000 Subject: [GHC] #7169: Warning for incomplete record field label used as function In-Reply-To: <047.31629c8fe32b813e38c132e8d4305995@haskell.org> References: <047.31629c8fe32b813e38c132e8d4305995@haskell.org> Message-ID: <062.1dbf5d3654659019c4e7dd5ec23521db@haskell.org> #7169: Warning for incomplete record field label used as function -------------------------------------+------------------------------------- Reporter: goldfire | Owner: nakaji_dayo Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.7 Resolution: | Keywords: Warnings, | newcomer Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by nakaji_dayo): * owner: (none) => nakaji_dayo Comment: I try to implement this. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jun 22 09:01:06 2017 From: ghc-devs at haskell.org (GHC) Date: Thu, 22 Jun 2017 09:01:06 -0000 Subject: [GHC] #13861: Take more advantage of STG representation invariance (follows up #9291) Message-ID: <048.651e325a747e822318af666cede88e81@haskell.org> #13861: Take more advantage of STG representation invariance (follows up #9291) -------------------------------------+------------------------------------- Reporter: heisenbug | Owner: (none) Type: feature | Status: new request | Priority: normal | Milestone: Component: Compiler | Version: 8.0.2 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- Consider following `case` alternatives at the STG stage (i.e. untyped) : {{{#!hs case scrut of False -> [] Just x -> Right x [] -> Nothing }}} The common theme of all these is that the scrutinee's memory layout and the result's memory layout coincide. So operationally no allocation needs to take place, and the whole `case` expression is simply a (strict) identity at the STG stage. I propose to add a small STG analysis to: * for each `case` alternative check whether the assigned tag between scrutinee and result matches, and if so * check whether both have the underlying memory layout and contents. If these conditions are met, the case alternative can be replaced with the identity. When all alternatives simplify to the identity (also considering the DEFAULT alternative), then the entire `case` expression reduces to a single identity DEFAULT alternative (i.e. all other alternatives in the `case` can be dropped). Many of the code examples in the join points paper (https://www.microsoft.com/en-us/research/wp-content/uploads/2016/11/join- points-pldi17.pdf) exhibit these optimisation opportunities. The already implemented suggestion in #9291 comes with the restriction that it only operates in the scope of the same type (see last comment there), but STG is untyped, so why not take advantage of this fact? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jun 22 09:19:08 2017 From: ghc-devs at haskell.org (GHC) Date: Thu, 22 Jun 2017 09:19:08 -0000 Subject: [GHC] #13861: Take more advantage of STG representation invariance (follows up #9291) In-Reply-To: <048.651e325a747e822318af666cede88e81@haskell.org> References: <048.651e325a747e822318af666cede88e81@haskell.org> Message-ID: <063.9f0b97e8d1ee28b062579e07ce29c603@haskell.org> #13861: Take more advantage of STG representation invariance (follows up #9291) -------------------------------------+------------------------------------- Reporter: heisenbug | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): Things to think about * It's not just memory layout. To substitute one data constructor for another, they must have the same ''tag''; and may even need to belong to a data type with the same number of data constructors. Eg {{{ case x of Nothing -> True }}} `Nothing` has tag zero, and `True` has tag 1. * Runtime debugging or heap analysis may display the data constructor. Substituting a data constructor from another type would break this utterly. I'd need a bit of convincing that the benefit (in performance) justified the cost; and that the opportunities to exploit this happen often enough to use worth doing. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jun 22 09:52:25 2017 From: ghc-devs at haskell.org (GHC) Date: Thu, 22 Jun 2017 09:52:25 -0000 Subject: [GHC] #9291: Don't reconstruct sum types if the type subtly changes In-Reply-To: <046.746d0dfe65f722505ddbecfcd76b7b95@haskell.org> References: <046.746d0dfe65f722505ddbecfcd76b7b95@haskell.org> Message-ID: <061.aa161f7ecefd11ff5b98fda9eb61a1a0@haskell.org> #9291: Don't reconstruct sum types if the type subtly changes -------------------------------------+------------------------------------- Reporter: schyler | Owner: nomeata Type: feature request | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 7.8.2 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2871 Wiki Page: | -------------------------------------+------------------------------------- Comment (by heisenbug): Replying to [comment:48 heisenbug]: I followed up with #13861 on this. Let's see what people think :-) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jun 22 09:59:29 2017 From: ghc-devs at haskell.org (GHC) Date: Thu, 22 Jun 2017 09:59:29 -0000 Subject: [GHC] #13861: Take more advantage of STG representation invariance (follows up #9291) In-Reply-To: <048.651e325a747e822318af666cede88e81@haskell.org> References: <048.651e325a747e822318af666cede88e81@haskell.org> Message-ID: <063.a4487c4476328e739d9be8f8f8fce10d@haskell.org> #13861: Take more advantage of STG representation invariance (follows up #9291) -------------------------------------+------------------------------------- Reporter: heisenbug | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by heisenbug): Replying to [comment:1 simonpj]: > Things to think about > > * It's not just memory layout. To substitute one data constructor for another, they must have the same ''tag''; and may even need to belong to a data type with the same number of data constructors. Eg Oh, yes I consider tags in my proposal. See my first bullet point. I doubt that the number of constructors must match, though. Maybe with nomeata's help I can come up with a proof-of-concept at some hackathon, so that we can get a feeling whether this optimisation kicks in often enough to become interesting. > {{{ > case x of > Nothing -> True > }}} > `Nothing` has tag zero, and `True` has tag 1. > > * Runtime debugging or heap analysis may display the data constructor. Substituting a data constructor from another type would break this utterly. > > I'd need a bit of convincing that the benefit (in performance) justified the cost; and that the opportunities to exploit this happen often enough to use worth doing. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jun 22 11:05:47 2017 From: ghc-devs at haskell.org (GHC) Date: Thu, 22 Jun 2017 11:05:47 -0000 Subject: [GHC] #12119: Can't create injective type family equation with TypeError as the RHS In-Reply-To: <050.21d4af732cea81fafcb58c894bb8137c@haskell.org> References: <050.21d4af732cea81fafcb58c894bb8137c@haskell.org> Message-ID: <065.a01a206735fbb11f46d5caf0583439a8@haskell.org> #12119: Can't create injective type family equation with TypeError as the RHS -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.1 checker) | Keywords: Resolution: | CustomTypeErrors, TypeFamilies, | InjectiveFamilies Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): > Of course, there's still Simon's point about formalizing this idea, which I have yet to do. Yes: formalising it at least into a GHC propoosal would be good: it's a user-facing change. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jun 22 11:11:00 2017 From: ghc-devs at haskell.org (GHC) Date: Thu, 22 Jun 2017 11:11:00 -0000 Subject: [GHC] #13680: Can't use TypeApplications with [] data constructor In-Reply-To: <050.c0d4ac8e4bffb622e3af6a2ccf399ea9@haskell.org> References: <050.c0d4ac8e4bffb622e3af6a2ccf399ea9@haskell.org> Message-ID: <065.6af79d19d0487d48306d497296232609@haskell.org> #13680: Can't use TypeApplications with [] data constructor -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.1 checker) | Keywords: Resolution: | TypeApplications Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * cc: goldfire (added) Comment: Richard is the king of visible type application, but he's on holiday for a fortnight. But I think you are right that the empty-list case of `ExplicitList` probably needs to be special-case. Should not be too hard to do that. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jun 22 12:14:30 2017 From: ghc-devs at haskell.org (GHC) Date: Thu, 22 Jun 2017 12:14:30 -0000 Subject: [GHC] #13862: Optional "-v" not allowed with :load in GHCi Message-ID: <044.9738400eba372a90ccdc97dcca61b7c9@haskell.org> #13862: Optional "-v" not allowed with :load in GHCi -------------------------------------+------------------------------------- Reporter: vanto | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: GHCi | Version: 8.0.2 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: Incorrect Unknown/Multiple | error/warning at compile-time Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- When loading a file in GHCi with the command {{{:load}}} and the file must import another file, if that other file is unavailable then GHCi sends the following error\\ {{{ Failed to load interface for `xxx` Use -v to see a list of the files searched for. }}} ' xxx ' is the name of the imported file that GHCi cannot find.\\ But we can not use a flag ( ie -v) with the command {{{:load}}} in GHCi.\\ This error is not appropriate in GHCi when using {{{:load}}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jun 22 14:53:21 2017 From: ghc-devs at haskell.org (GHC) Date: Thu, 22 Jun 2017 14:53:21 -0000 Subject: [GHC] #13847: record construction accepts local unqualified name instead of qualified imported name In-Reply-To: <049.a967f3782f78e925a6ef9e3030f47afd@haskell.org> References: <049.a967f3782f78e925a6ef9e3030f47afd@haskell.org> Message-ID: <064.20d2c6726d6495b9b1fcf37e525f264f@haskell.org> #13847: record construction accepts local unqualified name instead of qualified imported name -------------------------------------+------------------------------------- Reporter: j.waldmann | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC accepts | Unknown/Multiple invalid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by adamgundry): Mea culpa. I'll try to take a look at this at some point, but my spare cycles are desperately limited at the moment, so if someone else wants to jump in first then feel free. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jun 22 15:26:19 2017 From: ghc-devs at haskell.org (GHC) Date: Thu, 22 Jun 2017 15:26:19 -0000 Subject: [GHC] #13295: Failure to resolve type parameter determined by type family In-Reply-To: <048.831721c5435ed137cf42aa5ede0ed4ab@haskell.org> References: <048.831721c5435ed137cf42aa5ede0ed4ab@haskell.org> Message-ID: <063.fd71291e8bc37115ac42fa775f516305@haskell.org> #13295: Failure to resolve type parameter determined by type family -------------------------------------+------------------------------------- Reporter: alexvieth | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.1 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * cc: RyanGlScott (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jun 22 15:27:01 2017 From: ghc-devs at haskell.org (GHC) Date: Thu, 22 Jun 2017 15:27:01 -0000 Subject: [GHC] #12088: Type/data family instances in kind checking In-Reply-To: <048.155fdb7e7ce6e09c92258c376a6950ab@haskell.org> References: <048.155fdb7e7ce6e09c92258c376a6950ab@haskell.org> Message-ID: <063.2c84a3442ab47c1c41eb59bcf6298c9b@haskell.org> #12088: Type/data family instances in kind checking -------------------------------------+------------------------------------- Reporter: alexvieth | Owner: (none) Type: bug | Status: new Priority: high | Milestone: 8.4.1 Component: Compiler (Type | Version: 8.1 checker) | Resolution: | Keywords: TypeInType Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: #11348, #12239, | Differential Rev(s): Phab:D2272 #12643, #13790 | Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * cc: RyanGlScott (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jun 22 15:27:26 2017 From: ghc-devs at haskell.org (GHC) Date: Thu, 22 Jun 2017 15:27:26 -0000 Subject: [GHC] #12643: class declaration works in ghci, but not in a file In-Reply-To: <044.c716074b77b054579b7d856a68677406@haskell.org> References: <044.c716074b77b054579b7d856a68677406@haskell.org> Message-ID: <059.7f87eed120c603c95c184e6dd9e55671@haskell.org> #12643: class declaration works in ghci, but not in a file -------------------------------------+------------------------------------- Reporter: dmwit | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * cc: RyanGlScott (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jun 22 15:35:53 2017 From: ghc-devs at haskell.org (GHC) Date: Thu, 22 Jun 2017 15:35:53 -0000 Subject: [GHC] #13834: Error cascade with type applications In-Reply-To: <049.1249ca55bb94d4476098b14993c34065@haskell.org> References: <049.1249ca55bb94d4476098b14993c34065@haskell.org> Message-ID: <064.a111d0848f04b0b2716ec37914e3d75a@haskell.org> #13834: Error cascade with type applications -------------------------------------+------------------------------------- Reporter: mpickering | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: newcomer, | TypeApplications Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): Trac #13834 Here is what is happening: * The `Cannot apply expression..." error is spat out immediately, during constraint generation, not by `TcErrors` * The `Variable not in scope..` error is deferred; we spit out a constraint (a `CHoleCan` in fact). The constraint solver does its work; doing so will not solve the `CHoleCan`, but it often /does/ figure out what type the out-of-scope variable should have. The error is finally reported by `TcErrors`, when it reports errors from unsolved constraints Fixing this would be possible but fiddly. The obvious thing would be to add a new form of constraint, or generalise `CHoleCan`, to allow the "Cannot apply" error to be deferred. Then the error-message-prioritisation scheme in `TcErrors` could give the out-of-scope error priority over the cannot-apply one. If we did this, it should probably be just part of a generic way of deferring error messages. There are othe errors that are spat out immediately rather than going through the constraint solver. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jun 22 15:37:49 2017 From: ghc-devs at haskell.org (GHC) Date: Thu, 22 Jun 2017 15:37:49 -0000 Subject: [GHC] #13851: Change in specialisation(?) behaviour since 8.0.2 causes 6x slowdown In-Reply-To: <049.12eb233680e8d62e08f397274c91a741@haskell.org> References: <049.12eb233680e8d62e08f397274c91a741@haskell.org> Message-ID: <064.fd7236578a7fc497645cb9d102fd8833@haskell.org> #13851: Change in specialisation(?) behaviour since 8.0.2 causes 6x slowdown -------------------------------------+------------------------------------- Reporter: mpickering | Owner: (none) Type: bug | Status: new Priority: high | Milestone: 8.2.1 Component: Compiler | Version: 8.2.1-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): Here is what is happening * Before float-out we have {{{ $stest1mtl = \eta. ...foldr (\x k z. blah) z e... }}} Since the first arg of the foldr has no free vars, we float it out to give {{{ lvl = \x y z. blah $stest1mtl = \eta. ...foldr lvl z e... }}} * That makes `$stest1mtl` small, so it is inlined at its two call sites (the first two test case in `main`). * So now there are two calls to `lvl`, and it is quite big, so it doesn't get inlined. * But actually it is much better ''not'' to inline `$stest1mtl`, and instead (after the foldr/build stuff has happened) to inline `lvl` back into it. This kind of thing not new; I trip over it quite often. Generally, given {{{ f = e g = ...f.. h = ...g...g..f... }}} should we inline `f` into `g`, thereby making `g` big, so it doesn't inline into `h`? Or should we instead inline `g` into `h`? Sometimes one is better, sometimes the other; I don't know any systematic way of doing The Right Thing all the time. It turned out that the early-inline patch changed the choice, which resulted in the changed performance. However I did spot several things worth trying out * In `CoreArity.rhsEtaExpandArity` we carefully do not eta-expand thunks. But I saw some thunks like {{{ lvl_s621 = case z_a4NJ of wild_a4OF { GHC.Types.I# x1_a4OH -> case x_a4NH of wild1_a4OJ { GHC.Types.I# y1_a4OL -> case GHC.Prim.<=# x1_a4OH y1_a4OL of { __DEFAULT -> (\ _ (eta_B1 :: Int) -> (wild_a4OF, eta_B1)) 1# -> (\ _ (eta_B1 :: Int) -> (wild1_a4OJ, eta_B1)) }}} Here it really would be good to eta-expand; then that particular `lvl` could be inlined at its call sites. Here's a change to `CoreArity.rhsEtaExpandArity` that did the job: {{{ - | isOneShotInfo os || has_lam e -> 1 + length oss + | isOneShotInfo os || not (is_app e) -> 1 + length oss - has_lam (Tick _ e) = has_lam e - has_lam (Lam b e) = isId b || has_lam e - has_lam _ = False + is_app (Tick _ e) = is_app e + is_app (App f _) = is_app f + is_app (Var _) = True + is_app _ = False }}} Worth trying. * Now the offending top-level `lvl` function is still not inlined; but it has a function argument that is applied, so teh call sites look like {{{ lvl ... (\ab. blah) ... }}} When considering inining we do get a discount for the application of the argument inside `lvl`'s rhs, but it was only a discout of 60, which seems small considering how great it is to inline a function. Boosting it to 150 with `-funfolding-fun-discount=150` make the function inline, and we get good code all round. Maybe we should just up the default. * All the trouble is caused by the early float-out. I think we could try just elminating it. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jun 22 15:38:49 2017 From: ghc-devs at haskell.org (GHC) Date: Thu, 22 Jun 2017 15:38:49 -0000 Subject: [GHC] #13851: Change in specialisation(?) behaviour since 8.0.2 causes 6x slowdown In-Reply-To: <049.12eb233680e8d62e08f397274c91a741@haskell.org> References: <049.12eb233680e8d62e08f397274c91a741@haskell.org> Message-ID: <064.73c08c31ac7d44479f23ee39045279ab@haskell.org> #13851: Change in specialisation(?) behaviour since 8.0.2 causes 6x slowdown -------------------------------------+------------------------------------- Reporter: mpickering | Owner: (none) Type: bug | Status: new Priority: high | Milestone: 8.2.1 Component: Compiler | Version: 8.2.1-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): Based on this diagnosis, I don't think we should hold up the release. It's not a bug in pass X that can readily be fixed; it's the (very difficult) challenge of making correct inlining decisions. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jun 22 15:39:10 2017 From: ghc-devs at haskell.org (GHC) Date: Thu, 22 Jun 2017 15:39:10 -0000 Subject: [GHC] #13851: Change in specialisation(?) behaviour since 8.0.2 causes 6x slowdown In-Reply-To: <049.12eb233680e8d62e08f397274c91a741@haskell.org> References: <049.12eb233680e8d62e08f397274c91a741@haskell.org> Message-ID: <064.6473b546db9bba96bd59e18ff820bbb8@haskell.org> #13851: Change in specialisation(?) behaviour since 8.0.2 causes 6x slowdown -------------------------------------+------------------------------------- Reporter: mpickering | Owner: (none) Type: bug | Status: new Priority: high | Milestone: 8.4.1 Component: Compiler | Version: 8.2.1-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * milestone: 8.2.1 => 8.4.1 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jun 22 15:40:07 2017 From: ghc-devs at haskell.org (GHC) Date: Thu, 22 Jun 2017 15:40:07 -0000 Subject: [GHC] #13834: Error cascade with type applications In-Reply-To: <049.1249ca55bb94d4476098b14993c34065@haskell.org> References: <049.1249ca55bb94d4476098b14993c34065@haskell.org> Message-ID: <064.caee0c2570b80a0c8d3b3e41d6efcb3e@haskell.org> #13834: Error cascade with type applications -------------------------------------+------------------------------------- Reporter: mpickering | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: newcomer, | TypeApplications, TypeErrorMessages Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * keywords: newcomer, TypeApplications => newcomer, TypeApplications, TypeErrorMessages -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jun 22 16:16:07 2017 From: ghc-devs at haskell.org (GHC) Date: Thu, 22 Jun 2017 16:16:07 -0000 Subject: [GHC] #13841: ADOPT pragma for silencing orphan instances warnings per instance In-Reply-To: <049.5c7de5285a14f8dfadfcf646791f0efd@haskell.org> References: <049.5c7de5285a14f8dfadfcf646791f0efd@haskell.org> Message-ID: <064.c05e2804d53bc6673cae664ad75a8124@haskell.org> #13841: ADOPT pragma for silencing orphan instances warnings per instance -------------------------------------+------------------------------------- Reporter: cocreature | Owner: (none) Type: feature request | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 8.3 Resolution: wontfix | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #602, #10150 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by cocreature): * status: new => closed * resolution: => wontfix Comment: Replying to [comment:2 RyanGlScott]: > Let me offer a dissenting opinion. I don't think we should be introducing tailor-made pragmas to suppress certain warnings like this. If we are in the business of suppressing warnings, we really should have a general mechanism that could work for //any// warning by delimiting regions of code that should have the warning disabled (the subject of #602). IMO, anything less than this is asking for trouble down the road. > > Moreover, I'm not a fan of changing the syntax of instances themselves just for the purposes of warning generation. We already have at least one pragma you can put in the same position, so now this would lead to pragma noise like: > > {{{#!hs > instance {-# OVERLAPPING #-} {-# ADOPT #-} C T > }}} > > In addition, we'd have to update the GHC and Template Haskell ASTs to support this, and I don't think what this buys us is worth the cost. You’re raising some good points here. My reasoning was that orphan instance warnings are different from most other warnings since you are often in a situation where you ''can’t'' fix it rather than just not wanting to fix it. Also I was hoping that by sidestepping the issues and questions accompanying we might get a significantly simpler implementation and can thereby get this feature a lot quicker. However, as you’ve correctly pointed out it’s not as simple as I’ve thought since it also affects TH so after considering all of this, I think it’s better to just focus the efforts on disabling warnings locally and will try to work on that myself so I’m closing this issue. Thanks for your comments! -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jun 22 17:11:09 2017 From: ghc-devs at haskell.org (GHC) Date: Thu, 22 Jun 2017 17:11:09 -0000 Subject: [GHC] #13862: Optional "-v" not allowed with :load in GHCi In-Reply-To: <044.9738400eba372a90ccdc97dcca61b7c9@haskell.org> References: <044.9738400eba372a90ccdc97dcca61b7c9@haskell.org> Message-ID: <059.d84006823845dcc8b33256843b60a931@haskell.org> #13862: Optional "-v" not allowed with :load in GHCi -------------------------------------+------------------------------------- Reporter: vanto | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: GHCi | Version: 8.0.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple error/warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): `-v` here refers to the command line argument, which can be set in GHCi using `:set -v`. While it would be nice if the error would suggest this, I don't see a way to make this so without a fairly significant amount of refactoring. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jun 22 17:19:31 2017 From: ghc-devs at haskell.org (GHC) Date: Thu, 22 Jun 2017 17:19:31 -0000 Subject: [GHC] #13863: -fno-code is broken on package:language-c-quote Message-ID: <043.24c6df62c4ee22a450d0662d44837518@haskell.org> #13863: -fno-code is broken on package:language-c-quote -------------------------------------+------------------------------------- Reporter: duog | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.3 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- reported by awson here: [https://github.com/haskell/haddock/issues/640#issuecomment-310442454] I think this is because QuasiQuotes should trigger object code generation. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jun 22 17:20:34 2017 From: ghc-devs at haskell.org (GHC) Date: Thu, 22 Jun 2017 17:20:34 -0000 Subject: [GHC] #13863: -fno-code is broken on package:language-c-quote In-Reply-To: <043.24c6df62c4ee22a450d0662d44837518@haskell.org> References: <043.24c6df62c4ee22a450d0662d44837518@haskell.org> Message-ID: <058.661cf619ef46a4296705891a264bcad4@haskell.org> #13863: -fno-code is broken on package:language-c-quote -------------------------------------+------------------------------------- Reporter: duog | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Description changed by duog: @@ -2,1 +2,1 @@ - [https://github.com/haskell/haddock/issues/640#issuecomment-310442454] + [https://github.com/haskell/haddock/issues/640] New description: reported by awson here: [https://github.com/haskell/haddock/issues/640] I think this is because QuasiQuotes should trigger object code generation. -- -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jun 22 17:48:13 2017 From: ghc-devs at haskell.org (GHC) Date: Thu, 22 Jun 2017 17:48:13 -0000 Subject: [GHC] #13862: Optional "-v" not allowed with :load in GHCi In-Reply-To: <044.9738400eba372a90ccdc97dcca61b7c9@haskell.org> References: <044.9738400eba372a90ccdc97dcca61b7c9@haskell.org> Message-ID: <059.33291594aeaf222e1fe21fee5e610c76@haskell.org> #13862: Optional "-v" not allowed with :load in GHCi -------------------------------------+------------------------------------- Reporter: vanto | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: GHCi | Version: 8.0.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple error/warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by vanto): Hello Ben. I didn't express myself well. Actually if I use GHC (the compiler) the error is the same. ok! And if I compile the file with the {{{-v}}} option, GHC gives me a result. But you cannot use the {{{-v}}} option to have the same result with {{{:load}}} in GHCi (the interpreter).\\ That's why I say that this error message is not appropriate to be used in GHCi. This error message makes no sense here. Do you understand? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jun 22 18:07:01 2017 From: ghc-devs at haskell.org (GHC) Date: Thu, 22 Jun 2017 18:07:01 -0000 Subject: [GHC] #11962: Support induction recursion In-Reply-To: <047.045273ef2ac55a0385e215af795b4757@haskell.org> References: <047.045273ef2ac55a0385e215af795b4757@haskell.org> Message-ID: <062.b8aad7769058fcf6b45c8c1f59b015c7@haskell.org> #11962: Support induction recursion -------------------------------------+------------------------------------- Reporter: goldfire | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.1 Resolution: | Keywords: TypeInType Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * cc: RyanGlScott (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jun 22 18:41:36 2017 From: ghc-devs at haskell.org (GHC) Date: Thu, 22 Jun 2017 18:41:36 -0000 Subject: [GHC] #13862: Optional "-v" not allowed with :load in GHCi In-Reply-To: <044.9738400eba372a90ccdc97dcca61b7c9@haskell.org> References: <044.9738400eba372a90ccdc97dcca61b7c9@haskell.org> Message-ID: <059.ffc15e179668521ab10808ca6d206e8f@haskell.org> #13862: Optional "-v" not allowed with :load in GHCi -------------------------------------+------------------------------------- Reporter: vanto | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: GHCi | Version: 8.0.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple error/warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): Yes, I understand. You are correct that `:load` does not accept the `-v` flag. However, the user can use `:set -v` to achieve the end suggested in the error message. As I said above, it would be nice if the error message would specifically recommend that the user run `:set -v` instead of merely suggesting that they "Use -v". Do feel free to offer a patch. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jun 22 19:23:57 2017 From: ghc-devs at haskell.org (GHC) Date: Thu, 22 Jun 2017 19:23:57 -0000 Subject: [GHC] #13862: Optional "-v" not allowed with :load in GHCi In-Reply-To: <044.9738400eba372a90ccdc97dcca61b7c9@haskell.org> References: <044.9738400eba372a90ccdc97dcca61b7c9@haskell.org> Message-ID: <059.2c4e8ec12da51e746d31e9aeee8dc683@haskell.org> #13862: Optional "-v" not allowed with :load in GHCi -------------------------------------+------------------------------------- Reporter: vanto | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: GHCi | Version: 8.0.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple error/warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by vanto): Yes this is what one must write in the error message in GHCi. Thanks Ben, but I do not know how to do it. I think it will be too difficult for me. Sorry! -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jun 22 20:47:33 2017 From: ghc-devs at haskell.org (GHC) Date: Thu, 22 Jun 2017 20:47:33 -0000 Subject: [GHC] #12379: WARN pragma gives warning `warning: [-Wdeprecations]' In-Reply-To: <045.155a5978502e79d25fe769eea3d3ec0b@haskell.org> References: <045.155a5978502e79d25fe769eea3d3ec0b@haskell.org> Message-ID: <060.cb03e6d72624c499f8a489126f469395@haskell.org> #12379: WARN pragma gives warning `warning: [-Wdeprecations]' -------------------------------------+------------------------------------- Reporter: zilinc | Owner: (none) Type: bug | Status: closed Priority: low | Milestone: 8.2.1 Component: Documentation | Version: 8.0.1 Resolution: fixed | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: Type of failure: Documentation | Unknown/Multiple bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: merge => closed * resolution: => fixed Comment: Merged in 986deaa5539552f84b4f1d1872ae8a4c8240097e. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 23 00:12:47 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 23 Jun 2017 00:12:47 -0000 Subject: [GHC] #13863: -fno-code is broken on package:language-c-quote In-Reply-To: <043.24c6df62c4ee22a450d0662d44837518@haskell.org> References: <043.24c6df62c4ee22a450d0662d44837518@haskell.org> Message-ID: <058.e46b756ac42981ee7c2c7b2bfd7332e0@haskell.org> #13863: -fno-code is broken on package:language-c-quote -------------------------------------+------------------------------------- Reporter: duog | Owner: duog Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by duog): * owner: (none) => duog @@ -5,0 +5,2 @@ + + I am also concerned how this interacts with ANN pragmas. New description: reported by awson here: [https://github.com/haskell/haddock/issues/640] I think this is because QuasiQuotes should trigger object code generation. I am also concerned how this interacts with ANN pragmas. -- Comment: Replying to [ticket:13863 duog]: > reported by awson here: > [https://github.com/haskell/haddock/issues/640] > > I think this is because QuasiQuotes should trigger object code generation. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 23 01:00:05 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 23 Jun 2017 01:00:05 -0000 Subject: [GHC] #13864: RTS Stats are recorded without -T Message-ID: <044.9df229b07a94d2f8126cf8d8d9d18c67@haskell.org> #13864: RTS Stats are recorded without -T -------------------------------------+------------------------------------- Reporter: glguy | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Runtime | Version: 8.2.1-rc2 System | Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- The GHC.Stats module documents that I need to run my program with -T to generate stats, but I don't seem to need to. Perhaps the documentation is wrong or the stats are being collected when they shouldn't be. This is a regression(?) from GHC 8.0.2 where -T was required. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 23 08:05:46 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 23 Jun 2017 08:05:46 -0000 Subject: [GHC] #8177: Roles for type families In-Reply-To: <046.bd13b30db1cfd3d4628960446a01267b@haskell.org> References: <046.bd13b30db1cfd3d4628960446a01267b@haskell.org> Message-ID: <061.f023f15a96fffef70d8c4863e7e223d1@haskell.org> #8177: Roles for type families -------------------------------------+------------------------------------- Reporter: simonpj | Owner: goldfire Type: bug | Status: new Priority: normal | Milestone: ⊥ Component: Compiler | Version: 7.6.3 Resolution: | Keywords: TypeFamilies Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3662 Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): > I've uploaded a rough attempt at implementing support for roles for closed type families Great work! But I really would prefer to see a specification first :-). There's a lot of discussion on this thread about what the specification should even be. It's hard to review an implementation without a spec, covering * Syntax * Typing rules (at least in clear English) * Lots of examples Of course, we'd ultimately like a proof of soundness of the rules, but the "Richard thinks this is right" tests is at least a start. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 23 08:25:39 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 23 Jun 2017 08:25:39 -0000 Subject: [GHC] #13848: Unexpected order of variable quantification with GADT constructor In-Reply-To: <050.1bdc037c5d3daf9f53281904769def22@haskell.org> References: <050.1bdc037c5d3daf9f53281904769def22@haskell.org> Message-ID: <065.324ba46433752e733ee16900b031ebdd@haskell.org> #13848: Unexpected order of variable quantification with GADT constructor -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.1 checker) | Keywords: Resolution: | TypeApplications Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): Hmm. Fortunately we already have just the hook we need. Every interesting data constructor (including every GADT data con) has a wrapper; it is built by `MkId.mkDataConRep`. Look at `wrapper_reqd` to see which data cons have wrappers. The wrapper mediates between the nice user view of the data constructor and the internal "representation data constructor" that GHC uses internally. So for example {{{ data T a where MkT :: forall p q. p -> q -> T (p,q) }}} The representation data con has this type {{{ MkT :: forall r. forall p q. (r ~ (p,q)) => p -> q -> T r }}} But the wrapper is defined like this {{{ $WMkT :: forall p q. p -> q -> T (p,q) $WMkT = /\p q. \(x::p) (y::q). MkT @(p,q) @p @q <(p,q)> x y }}} The `<(p,q)>` is a coercion argument (refl) witnessing `(p,q)~(p,q)` Now currently `dataConUserType` (which claims to show the user-written type of the data con) is thus (in `DataCon`): {{{ dataConUserType (MkData { dcUnivTyVars = univ_tvs, dcExTyVars = ex_tvs, dcEqSpec = eq_spec, dcOtherTheta = theta, dcOrigArgTys = arg_tys, dcOrigResTy = res_ty }) = mkForAllTys (filterEqSpec eq_spec univ_tvs) $ mkForAllTys ex_tvs $ mkFunTys theta $ mkFunTys arg_tys $ res_ty }}} This `filterEqSpec` business is fishy! But now we understand about wrappers, for data constructors that have wrappers we could insead use the type of the wrapper, thus: {{{ dataConUserTYpe (MkData { dcRep = rep , dcRepType = rep_ty } = case rep of DCR { dcr_wrap_id = wrap_id } -> idType wrap_id NoDataConRep -> rep_ty -- If there is no wrapper, the "rep-type" is the same -- as the "user type" }}} Whizzo. Now, to return to the ticket, * We should ensure that the wrapper type reflects exactly the type the user wrote including type variable order * That in turn may force to make a wrapper when we don't right now, just to swizzle round the type variables Make sense? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 23 10:53:23 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 23 Jun 2017 10:53:23 -0000 Subject: [GHC] #13009: Hierarchical Module Structure for GHC In-Reply-To: <045.859215149771e4346ac45f933feca22e@haskell.org> References: <045.859215149771e4346ac45f933feca22e@haskell.org> Message-ID: <060.896073f69370f97494789635b0e1aa06@haskell.org> #13009: Hierarchical Module Structure for GHC -------------------------------------+------------------------------------- Reporter: hsyl20 | Owner: hsyl20 Type: task | Status: patch Priority: low | Milestone: Component: GHC API | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3647 Wiki Page: | ModuleDependencies/Hierarchical | -------------------------------------+------------------------------------- Comment (by hsyl20): The proposal: https://github.com/ghc-proposals/ghc-proposals/pull/57 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 23 11:16:49 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 23 Jun 2017 11:16:49 -0000 Subject: [GHC] #13865: Add to Data.Proxy a utility function proxy :: a -> Proxy a Message-ID: <047.75c63b556c59ec5776884ac4f61b6e30@haskell.org> #13865: Add to Data.Proxy a utility function proxy :: a -> Proxy a -------------------------------------+------------------------------------- Reporter: louispan | Owner: (none) Type: feature | Status: new request | Priority: normal | Milestone: 8.2.1 Component: | Version: 8.0.1 libraries/base | Keywords: Proxy | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- I sometime find myself wanting to create a Proxy of a certain type (to pass into functions that use Proxy), but I only have easy access to the value, but not the type (eg. because the type is being inferred). That is, I find myself defining the following function proxy :: a -> Proxy a proxy _ = Proxy It would be great if something like that could be added to Data.Proxy -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 23 11:18:14 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 23 Jun 2017 11:18:14 -0000 Subject: [GHC] #13865: Add to Data.Proxy a utility function proxy :: a -> Proxy a In-Reply-To: <047.75c63b556c59ec5776884ac4f61b6e30@haskell.org> References: <047.75c63b556c59ec5776884ac4f61b6e30@haskell.org> Message-ID: <062.ef793a8fd656c1b89615960e66048ee4@haskell.org> #13865: Add to Data.Proxy a utility function proxy :: a -> Proxy a -------------------------------------+------------------------------------- Reporter: louispan | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: 8.2.1 Component: libraries/base | Version: 8.0.1 Resolution: | Keywords: Proxy Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Description changed by louispan: @@ -6,0 +6,1 @@ + {{{#!haskell @@ -8,0 +9,1 @@ + }}} New description: I sometime find myself wanting to create a Proxy of a certain type (to pass into functions that use Proxy), but I only have easy access to the value, but not the type (eg. because the type is being inferred). That is, I find myself defining the following function {{{#!haskell proxy :: a -> Proxy a proxy _ = Proxy }}} It would be great if something like that could be added to Data.Proxy -- -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 23 11:40:42 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 23 Jun 2017 11:40:42 -0000 Subject: [GHC] #11343: Unable to infer type when using DuplicateRecordFields In-Reply-To: <049.6becc7f1facb1381b419a45f19851622@haskell.org> References: <049.6becc7f1facb1381b419a45f19851622@haskell.org> Message-ID: <064.ffa9baf05be4d7e0aa7688ce4d91fbba@haskell.org> #11343: Unable to infer type when using DuplicateRecordFields -------------------------------------+------------------------------------- Reporter: mpickering | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 7.11 checker) | Resolution: | Keywords: ORF Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by nh2): * cc: nh2 (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 23 12:16:58 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 23 Jun 2017 12:16:58 -0000 Subject: [GHC] #13866: -g doesn't work with -pgma=clang++ Message-ID: <046.0cc5ec25fa742bf402aa06da26adeede@haskell.org> #13866: -g doesn't work with -pgma=clang++ -------------------------------------+------------------------------------- Reporter: niteria | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.3 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- This is a follow-up to #11202. The fix there is platform specific, but the problem is compiler/assembler specific. Sample of errors: {{{ /tmp/ghc4044980_0/ghc_2.s:681:2: error: error: unknown directive .hword 4 ^ | 681 | .hword 4 | ^ }}} Repro command: {{{ $ cat A.hs module A where main = putStrLn "Hello" $ ./inplace/bin/ghc-stage2 -g -pgma=clang++ A.hs }}} One workaround that I've found: {{{ $ ./inplace/bin/ghc-stage2 -g -pgma=clang++ -opta=-no-integrated-as A.hs # succeeds }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 23 12:23:46 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 23 Jun 2017 12:23:46 -0000 Subject: [GHC] #13866: -g doesn't work with -pgma=clang++ In-Reply-To: <046.0cc5ec25fa742bf402aa06da26adeede@haskell.org> References: <046.0cc5ec25fa742bf402aa06da26adeede@haskell.org> Message-ID: <061.e929651baec5def105bdc71dad687052@haskell.org> #13866: -g doesn't work with -pgma=clang++ -------------------------------------+------------------------------------- Reporter: niteria | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by niteria): To be clear, this is on Linux with clang. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 23 13:34:24 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 23 Jun 2017 13:34:24 -0000 Subject: [GHC] #13865: Add to Data.Proxy a utility function proxy :: a -> Proxy a In-Reply-To: <047.75c63b556c59ec5776884ac4f61b6e30@haskell.org> References: <047.75c63b556c59ec5776884ac4f61b6e30@haskell.org> Message-ID: <062.29d03469200aa926bd6cc87ce96a648b@haskell.org> #13865: Add to Data.Proxy a utility function proxy :: a -> Proxy a -------------------------------------+------------------------------------- Reporter: louispan | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: 8.2.1 Component: libraries/base | Version: 8.0.1 Resolution: | Keywords: Proxy Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): Hi louispan, It's worth noting that `Proxy` is an instance of `Applicative`, so your proposed `proxy` function is simply `pure`. Does that address your needs? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 23 14:27:13 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 23 Jun 2017 14:27:13 -0000 Subject: [GHC] #13866: -g doesn't work with -pgma=clang++ In-Reply-To: <046.0cc5ec25fa742bf402aa06da26adeede@haskell.org> References: <046.0cc5ec25fa742bf402aa06da26adeede@haskell.org> Message-ID: <061.68c2b58ffc6ca8084b262f1fa1879f59@haskell.org> #13866: -g doesn't work with -pgma=clang++ -------------------------------------+------------------------------------- Reporter: niteria | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): This is an annoying inconsistency which I thought was only applicable to Darwin, but it seems I was wrong. See `nativeGen/DWARF/Types.hs:pprHalf`. Perhaps we just need to make this compiler depedent? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 23 14:28:08 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 23 Jun 2017 14:28:08 -0000 Subject: [GHC] #13866: -g doesn't work with -pgma=clang++ In-Reply-To: <046.0cc5ec25fa742bf402aa06da26adeede@haskell.org> References: <046.0cc5ec25fa742bf402aa06da26adeede@haskell.org> Message-ID: <061.598cd1d23aefb55a74883e71e9d11041@haskell.org> #13866: -g doesn't work with -pgma=clang++ ---------------------------------+---------------------------------------- Reporter: niteria | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.3 Resolution: | Keywords: Operating System: Linux | Architecture: Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | ---------------------------------+---------------------------------------- Changes (by bgamari): * os: Unknown/Multiple => Linux -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 23 14:45:29 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 23 Jun 2017 14:45:29 -0000 Subject: [GHC] #13867: Silly definitions remain after SpecConstr Message-ID: <046.4b2d8e03724e439f19d977c46f23f7aa@haskell.org> #13867: Silly definitions remain after SpecConstr -------------------------------------+------------------------------------- Reporter: simonpj | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- Consider this {{{ f x xs = let g y = case y of [] -> 0 (a:as) -> g as in g (x:xs) }}} Compile with -O2 and we get this {{{ f = \ (@ t_axv) (@ a_axw) ($dNum_axx :: Num a_axw) (x_amR :: t_axv) (xs_amS :: [t_axv]) -> let { lvl_sxV [Dmd=] :: a_axw [LclId, Str=DmdType] lvl_sxV = fromInteger @ a_axw $dNum_axx Foo.f1 } in letrec { $sg_syr [Occ=LoopBreaker] :: t_axv -> [t_axv] -> a_axw [LclId, Arity=2, Str=DmdType ] $sg_syr = \ _ [Occ=Dead] (sc1_syq :: [t_axv]) -> g_sxS sc1_syq; g_sxS [Occ=LoopBreaker] :: [t_axv] -> a_axw [LclId, Arity=1, Str=DmdType ] g_sxS = \ (y_amU :: [t_axv]) -> case y_amU of _ [Occ=Dead] { [] -> lvl_sxV; : a1_amV as_amW -> g_sxS as_amW }; } in $sg_syr x_amR xs_amS }}} Look at that stupid `$sg_syr` function. It should jolly well be inlined at its only call site. But it isn't because it's a loop breaker? Why is it a loop breaker? Because earlier there was a RULE for `g` that mentioned `$sg`. This is stupid. It's not killing us but it is obviously wrong. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 23 15:46:33 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 23 Jun 2017 15:46:33 -0000 Subject: [GHC] #13868: Improved help suggested in the error message about "import". Message-ID: <044.12cc8180b29f5f32da7d3cc0d265d7d4@haskell.org> #13868: Improved help suggested in the error message about "import". -------------------------------------+------------------------------------- Reporter: vanto | Owner: (none) Type: feature | Status: new request | Priority: normal | Milestone: Component: Compiler | Version: 8.0.2 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: Poor/confusing Unknown/Multiple | error message Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- I know that improving error messages is a headache in Haskell. But we still need to point out the mistakes or the nonsense. Here are some examples of import test "module" at the beginning of the program (any). I randomly chose the "Data" module. Below each import, the response from GHC. And below, my opinion.\\ {{{ import Data.Aaa Failed to load interface for `Data.Aaa' Perhaps you meant Data.Data (from base-4.9.1.0) Data.Map (from containers-0.5.7.1) }}} No relationship.\\ {{{ import Data.Bbb Failed to load interface for `Data.Bbb' }}} Ok.\\ {{{ import Data.Ccc Failed to load interface for `Data.Ccc' }}} Ok.\\ {{{ import Data.Ddd Failed to load interface for `Data.Ddd' Perhaps you meant Data.Ord (from base-4.9.1.0) }}} No relationship.\\ {{{ import Data.Eee Failed to load interface for `Data.Eee' Perhaps you meant Data.Eq (from base-4.9.1.0) Data.Set (from containers-0.5.7.1) Data.Tree (from containers-0.5.7.1) }}} No relationship.\\ I stopped looking because I do not know how to correct it. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 23 16:03:05 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 23 Jun 2017 16:03:05 -0000 Subject: [GHC] #13867: Silly definitions remain after SpecConstr In-Reply-To: <046.4b2d8e03724e439f19d977c46f23f7aa@haskell.org> References: <046.4b2d8e03724e439f19d977c46f23f7aa@haskell.org> Message-ID: <061.4de8b0be00337de81ce969432aa17899@haskell.org> #13867: Silly definitions remain after SpecConstr -------------------------------------+------------------------------------- Reporter: simonpj | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: SpecConstr Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by mpickering): * cc: mpickering (added) * keywords: => SpecConstr -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 23 16:13:01 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 23 Jun 2017 16:13:01 -0000 Subject: [GHC] #13869: Improved response from GHCi about ":l" or ":r". Message-ID: <044.9749f3a4765073f51a83123d27d51a4f@haskell.org> #13869: Improved response from GHCi about ":l" or ":r". -------------------------------------+------------------------------------- Reporter: vanto | Owner: (none) Type: feature | Status: new request | Priority: normal | Milestone: Component: GHCi | Version: 8.0.2 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: Incorrect Unknown/Multiple | error/warning at compile-time Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- I inadvertently wrote {{{:l}}} instead of {{{:r}}} and after typing on "return" GHCi replied\\ {{{ Prelude> :l Ok, modules loaded: none. }}} It disturbed me for a few moments. Why OK? Sorry but again this does not make sense here. The interpreter does not load anything. It is better to say\\ {{{ Failed, modules loaded: none. }}} And so after I write\\ {{{ Prelude> :r Ok, modules loaded: none. }}} Here too it is better to say\\ {{{ Failed, modules loaded: none. }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 23 16:57:36 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 23 Jun 2017 16:57:36 -0000 Subject: [GHC] #12356: StaticPointers support in GHCi In-Reply-To: <046.4add1b1a872a2608a03a4c2efa3faa77@haskell.org> References: <046.4add1b1a872a2608a03a4c2efa3faa77@haskell.org> Message-ID: <061.0db2910ac6ef951da9262fdfa9d49c39@haskell.org> #12356: StaticPointers support in GHCi -------------------------------------+------------------------------------- Reporter: bgamari | Owner: (none) Type: feature request | Status: merge Priority: normal | Milestone: 8.2.1 Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #12000, #9878 | Differential Rev(s): Phab:D2504, Wiki Page: | Phab:D3663 -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => merge -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 23 17:00:07 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 23 Jun 2017 17:00:07 -0000 Subject: [GHC] #13856: "Zero-argument" lambda expressions from pretty-print strangely In-Reply-To: <050.0d7c2840d6bcad243ed441cfec14dd9f@haskell.org> References: <050.0d7c2840d6bcad243ed441cfec14dd9f@haskell.org> Message-ID: <065.db3933a70212b900d28598678b6b335e@haskell.org> #13856: "Zero-argument" lambda expressions from pretty-print strangely -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.4.1 Component: Template Haskell | Version: 8.0.1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3664 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: patch => closed * resolution: => fixed * milestone: => 8.4.1 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 23 17:07:48 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 23 Jun 2017 17:07:48 -0000 Subject: [GHC] #12356: StaticPointers support in GHCi In-Reply-To: <046.4add1b1a872a2608a03a4c2efa3faa77@haskell.org> References: <046.4add1b1a872a2608a03a4c2efa3faa77@haskell.org> Message-ID: <061.cc2c17b6f43f1180a4ebb2c756d6f56c@haskell.org> #12356: StaticPointers support in GHCi -------------------------------------+------------------------------------- Reporter: bgamari | Owner: (none) Type: feature request | Status: merge Priority: normal | Milestone: 8.2.1 Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #12000, #9878 | Differential Rev(s): Phab:D2504, Wiki Page: | Phab:D3663 -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"84cf095dc981ea21fcceddbb71463dd7844754ca/ghc" 84cf095d/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="84cf095dc981ea21fcceddbb71463dd7844754ca" compiler: Eliminate pprTrace in SPT entry addition codepath Test Plan: Load program with StaticPointers into GHCi, ensure no tracing output makes it in. Reviewers: austin Subscribers: rwbarton, thomie, RyanGlScott GHC Trac Issues: #12356 Differential Revision: https://phabricator.haskell.org/D3663 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 23 17:07:48 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 23 Jun 2017 17:07:48 -0000 Subject: [GHC] #11224: Program doesn't preserve semantics after pattern synonym inlining. In-Reply-To: <052.0e88dfcc1c4328e2f98c2a5296a41d5b@haskell.org> References: <052.0e88dfcc1c4328e2f98c2a5296a41d5b@haskell.org> Message-ID: <067.ea86311bc1cd8d34d388a7f6923bf563@haskell.org> #11224: Program doesn't preserve semantics after pattern synonym inlining. -------------------------------------+------------------------------------- Reporter: anton.dubovik | Owner: (none) Type: bug | Status: closed Priority: highest | Milestone: 8.0.1 Component: Compiler | Version: 7.10.2 Resolution: fixed | Keywords: | PatternSynonyms Operating System: Windows | Architecture: x86_64 | (amd64) Type of failure: Incorrect result | Test Case: at runtime | patsyn/should_run/T11224 Blocked By: | Blocking: Related Tickets: #11225 | Differential Rev(s): Phab:D1632 Wiki Page: | -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"9077120918b78f5152bf3596fe6df07b91cead79/ghc" 90771209/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="9077120918b78f5152bf3596fe6df07b91cead79" Use actual universal tvs in check for naughty record selectors The naughty record selector check means to limit selectors which would lead to existential tyvars escaping their scope. With record pattern synonyms, there are situations where universal tyvars don't appear in the result type, for example: ``` pattern ReadP :: Read a => a -> String pattern ReadP{readp} <- (read -> readp) ``` This is a similar issue to #11224 where we assumed that we can decide which variables are universal and which are existential by the syntactic check of seeing which appear in the result type. The fix is to use `univ_tvs` from `conLikeFullSig` rather than the previous approximation. But we must also remember to apply `EqSpec`s so we use the free variables from `inst_tys` which is precisely `univ_tvs` with `EqSpecs` applied. Reviewers: austin, bgamari Reviewed By: bgamari Subscribers: rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D3649 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 23 17:07:48 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 23 Jun 2017 17:07:48 -0000 Subject: [GHC] #13856: "Zero-argument" lambda expressions from pretty-print strangely In-Reply-To: <050.0d7c2840d6bcad243ed441cfec14dd9f@haskell.org> References: <050.0d7c2840d6bcad243ed441cfec14dd9f@haskell.org> Message-ID: <065.2563ff289cca9eabc017db8333f8a1a8@haskell.org> #13856: "Zero-argument" lambda expressions from pretty-print strangely -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.4.1 Component: Template Haskell | Version: 8.0.1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3664 Wiki Page: | -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"3c4537ea1c940966eddcb9cb418bf8e39b8f0f1c/ghc" 3c4537ea/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="3c4537ea1c940966eddcb9cb418bf8e39b8f0f1c" Fix pretty-printing of zero-argument lambda expressions Using Template Haskell, one can construct lambda expressions with no arguments. The pretty-printer isn't aware of this fact, however. This changes that. Test Plan: make test TEST=T13856 Reviewers: bgamari, austin, goldfire Reviewed By: bgamari Subscribers: rwbarton, thomie GHC Trac Issues: #13856 Differential Revision: https://phabricator.haskell.org/D3664 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 23 17:17:30 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 23 Jun 2017 17:17:30 -0000 Subject: [GHC] #13868: Improved help suggested in the error message about "import". In-Reply-To: <044.12cc8180b29f5f32da7d3cc0d265d7d4@haskell.org> References: <044.12cc8180b29f5f32da7d3cc0d265d7d4@haskell.org> Message-ID: <059.f8f07c195422d5efeab506408c5a60ea@haskell.org> #13868: Improved help suggested in the error message about "import". -------------------------------------+------------------------------------- Reporter: vanto | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Poor/confusing | Unknown/Multiple error message | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): What would you like GHC to say in these cases? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 23 18:00:54 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 23 Jun 2017 18:00:54 -0000 Subject: [GHC] #13868: Improved help suggested in the error message about "import". In-Reply-To: <044.12cc8180b29f5f32da7d3cc0d265d7d4@haskell.org> References: <044.12cc8180b29f5f32da7d3cc0d265d7d4@haskell.org> Message-ID: <059.93b77f62fe08227b59b022c7e871214e@haskell.org> #13868: Improved help suggested in the error message about "import". -------------------------------------+------------------------------------- Reporter: vanto | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Poor/confusing | Unknown/Multiple error message | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by vanto): Well, look at this example.\\ {{{ import Data.Chat Failed to load interface for `Data.Chat' Perhaps you meant Data.Char (from base-4.9.1.0) Data.Char8 (from word8-0.1.2) }}} The response given by GHC is quite adequate. He answers what we expect from him. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 23 18:22:17 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 23 Jun 2017 18:22:17 -0000 Subject: [GHC] #13868: Improved help suggested in the error message about "import". In-Reply-To: <044.12cc8180b29f5f32da7d3cc0d265d7d4@haskell.org> References: <044.12cc8180b29f5f32da7d3cc0d265d7d4@haskell.org> Message-ID: <059.81ce3acfc3dad635dbd8497dd7e57227@haskell.org> #13868: Improved help suggested in the error message about "import". -------------------------------------+------------------------------------- Reporter: vanto | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Poor/confusing | Unknown/Multiple error message | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by hsyl20): In the examples you give, there may be relationships according to the fuzzy search algorithm (https://en.wikipedia.org/wiki/Damerau–Levenshtein_distance) and the current thresholds (cf [[GhcFile(compiler/utils/Util.hs#L950)]]). -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 23 18:52:10 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 23 Jun 2017 18:52:10 -0000 Subject: [GHC] #13782: Bullish use of Template Haskell's newName causes GHC internal error In-Reply-To: <050.355b0f2ffb6750de858fbc3a1ccc85be@haskell.org> References: <050.355b0f2ffb6750de858fbc3a1ccc85be@haskell.org> Message-ID: <065.d89c96d87ac40f5f971e5956e0afaee6@haskell.org> #13782: Bullish use of Template Haskell's newName causes GHC internal error -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: carlostome Type: bug | Status: closed Priority: high | Milestone: 8.2.1 Component: Template Haskell | Version: 8.0.1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: #12503 | Differential Rev(s): Phab:D3641 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: merge => closed * resolution: => fixed Comment: Merged with 05ae09c7fac3e82a0b651980080fc472eb15e995. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 23 18:52:47 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 23 Jun 2017 18:52:47 -0000 Subject: [GHC] #12356: StaticPointers support in GHCi In-Reply-To: <046.4add1b1a872a2608a03a4c2efa3faa77@haskell.org> References: <046.4add1b1a872a2608a03a4c2efa3faa77@haskell.org> Message-ID: <061.e06b42fe8af0f554fc36a406d84b0bc7@haskell.org> #12356: StaticPointers support in GHCi -------------------------------------+------------------------------------- Reporter: bgamari | Owner: (none) Type: feature request | Status: closed Priority: normal | Milestone: 8.2.1 Component: Compiler | Version: 8.0.1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #12000, #9878 | Differential Rev(s): Phab:D2504, Wiki Page: | Phab:D3663 -------------------------------------+------------------------------------- Changes (by bgamari): * status: merge => closed * resolution: => fixed Comment: Merged with 0fa0d6c2d64dc41783e04b5887f96a996a181d3b -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 23 19:45:13 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 23 Jun 2017 19:45:13 -0000 Subject: [GHC] #13838: -Wdeferred-type-errors; ghc: panic!; VoidRep; ((() -> ()) :: *) ~# (IO Any :: *) In-Reply-To: <044.5150fbc131040d8653d1692d9b8b36a2@haskell.org> References: <044.5150fbc131040d8653d1692d9b8b36a2@haskell.org> Message-ID: <059.dd4a49abb05b0c6325c1d5ae2219951c@haskell.org> #13838: -Wdeferred-type-errors; ghc: panic!; VoidRep; ((() -> ()) :: *) ~# (IO Any :: *) -------------------------------------+------------------------------------- Reporter: harry | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: #13292 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by harry): Although my distro ships version 8.0.2 now I still get a "ghc: panic! (the 'impossible' happened)" with this slightly more complex code but within ghci only: With "ghci -fdefer-type-errors" and this code: {{{#!hs bad1 :: [()] bad1 = num bad2 :: () bad2 = num num = 9 }}} the output: {{{ GHCi, version 8.0.2: http://www.haskell.org/ghc/ :? for help Prelude> :l ghc_bug_2.hs [1 of 1] Compiling Main ( ghc_bug_2.hs, interpreted ) ghc_bug_2.hs:2:8: warning: [-Wdeferred-type-errors] * Couldn't match expected type `[()]' with actual type `()' * In the expression: num In an equation for `bad1': bad1 = num ghc: panic! (the 'impossible' happened) (GHC version 8.0.2 for x86_64-unknown-linux): corePrepPgm [False] cobox_r196 = typeError @ 'VoidRep @ (() :: *) ~# ([()] :: *) "ghc_bug_2.hs:2:8: error:\n\ \ * Couldn't match expected type `[()]' with actual type `()'\n\ \ * In the expression: num\n\ \ In an equation for `bad1': bad1 = num\n\ \(deferred type error)"# Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug > }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 23 19:50:53 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 23 Jun 2017 19:50:53 -0000 Subject: [GHC] #12978: User guide section on AllowAmbiguousTypes should mention TypeApplications In-Reply-To: <049.971cd017bc2e9b4b982c4731f7c4e434@haskell.org> References: <049.971cd017bc2e9b4b982c4731f7c4e434@haskell.org> Message-ID: <064.95c945d3b14720dc0e5fd9b108710cb9@haskell.org> #12978: User guide section on AllowAmbiguousTypes should mention TypeApplications -------------------------------------+------------------------------------- Reporter: mpickering | Owner: erdeszt Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by erdeszt): * owner: (none) => erdeszt -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 23 20:04:03 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 23 Jun 2017 20:04:03 -0000 Subject: [GHC] #13838: -Wdeferred-type-errors on a program with main not of type IO () yields "main thread exited (uncaught exception)" (was: -Wdeferred-type-errors; ghc: panic!; VoidRep; ((() -> ()) :: *) ~# (IO Any :: *)) In-Reply-To: <044.5150fbc131040d8653d1692d9b8b36a2@haskell.org> References: <044.5150fbc131040d8653d1692d9b8b36a2@haskell.org> Message-ID: <059.9f574b9371544ada6f7a3bf88a42bd64@haskell.org> #13838: -Wdeferred-type-errors on a program with main not of type IO () yields "main thread exited (uncaught exception)" -------------------------------------+------------------------------------- Reporter: harry | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: #13292 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): Correct, that is entirely expected. To be clear: the GHC panic/Core Lint error bug exists in GHC 8.0.2, but not 8.2. However, a bug persists in GHC 8.2 where actually running the code yields `main thread exited (uncaught exception)`, which shouldn't happen. I'll update the title accordingly. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 23 20:13:13 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 23 Jun 2017 20:13:13 -0000 Subject: [GHC] #12978: User guide section on AllowAmbiguousTypes should mention TypeApplications In-Reply-To: <049.971cd017bc2e9b4b982c4731f7c4e434@haskell.org> References: <049.971cd017bc2e9b4b982c4731f7c4e434@haskell.org> Message-ID: <064.c4d5ac397722c70e9912a36257aaf766@haskell.org> #12978: User guide section on AllowAmbiguousTypes should mention TypeApplications -------------------------------------+------------------------------------- Reporter: mpickering | Owner: erdeszt Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3668 Wiki Page: | -------------------------------------+------------------------------------- Changes (by erdeszt): * differential: => Phab:D3668 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 23 20:35:09 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 23 Jun 2017 20:35:09 -0000 Subject: [GHC] #12978: User guide section on AllowAmbiguousTypes should mention TypeApplications In-Reply-To: <049.971cd017bc2e9b4b982c4731f7c4e434@haskell.org> References: <049.971cd017bc2e9b4b982c4731f7c4e434@haskell.org> Message-ID: <064.6d19acebb8361d8ecf9f1005fed3ee83@haskell.org> #12978: User guide section on AllowAmbiguousTypes should mention TypeApplications -------------------------------------+------------------------------------- Reporter: mpickering | Owner: erdeszt Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3668 Wiki Page: | -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"faefa7e57d543e7001457a53954c9b378a38ee60/ghc" faefa7e5/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="faefa7e57d543e7001457a53954c9b378a38ee60" documentation: fix trac issue #12978 Add reference to TypeApplications to the AllowAmbiguousType section of the user docs Reviewers: austin, bgamari Reviewed By: bgamari Subscribers: rwbarton, thomie GHC Trac Issues: #12978 Differential Revision: https://phabricator.haskell.org/D3668 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 23 20:43:41 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 23 Jun 2017 20:43:41 -0000 Subject: [GHC] #12978: User guide section on AllowAmbiguousTypes should mention TypeApplications In-Reply-To: <049.971cd017bc2e9b4b982c4731f7c4e434@haskell.org> References: <049.971cd017bc2e9b4b982c4731f7c4e434@haskell.org> Message-ID: <064.4c3c68ba6633bb28c60daacd21d5edca@haskell.org> #12978: User guide section on AllowAmbiguousTypes should mention TypeApplications -------------------------------------+------------------------------------- Reporter: mpickering | Owner: erdeszt Type: bug | Status: closed Priority: normal | Milestone: 8.2.1 Component: Compiler | Version: 8.0.1 Resolution: fixed | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3668 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => closed * resolution: => fixed * milestone: => 8.2.1 Comment: Merged to `ghc-8.2` as well. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 23 20:44:09 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 23 Jun 2017 20:44:09 -0000 Subject: [GHC] #13865: Add to Data.Proxy a utility function proxy :: a -> Proxy a In-Reply-To: <047.75c63b556c59ec5776884ac4f61b6e30@haskell.org> References: <047.75c63b556c59ec5776884ac4f61b6e30@haskell.org> Message-ID: <062.cdd25a66ab5a5677f6dc09a68fe3f84d@haskell.org> #13865: Add to Data.Proxy a utility function proxy :: a -> Proxy a -------------------------------------+------------------------------------- Reporter: louispan | Owner: (none) Type: feature request | Status: closed Priority: normal | Milestone: 8.2.1 Component: libraries/base | Version: 8.0.1 Resolution: invalid | Keywords: Proxy Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by louispan): * status: new => closed * resolution: => invalid Comment: Hi RyanGIScott, Oh my gosh, you are right. I never realized I could use (pure @Proxy) instead of that function. Thank you! I'll close this request. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 23 20:57:02 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 23 Jun 2017 20:57:02 -0000 Subject: [GHC] #13861: Take more advantage of STG representation invariance (follows up #9291) In-Reply-To: <048.651e325a747e822318af666cede88e81@haskell.org> References: <048.651e325a747e822318af666cede88e81@haskell.org> Message-ID: <063.8021c256d7a5809523bf4741e81f7f20@haskell.org> #13861: Take more advantage of STG representation invariance (follows up #9291) -------------------------------------+------------------------------------- Reporter: heisenbug | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by maoe): * cc: maoe (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 23 21:26:39 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 23 Jun 2017 21:26:39 -0000 Subject: [GHC] #13864: RTS Stats are recorded without -T In-Reply-To: <044.9df229b07a94d2f8126cf8d8d9d18c67@haskell.org> References: <044.9df229b07a94d2f8126cf8d8d9d18c67@haskell.org> Message-ID: <059.3826878bf53ce99800c56389097ea1d8@haskell.org> #13864: RTS Stats are recorded without -T -------------------------------------+------------------------------------- Reporter: glguy | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.2.1 Component: Runtime System | Version: 8.2.1-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * cc: DemiMarie (added) * milestone: => 8.2.1 Comment: Mmm, good catch. Indeed 12ad4d417b89462ba8e19a3c7772a931b3a93f0e (Throw an exception on heap overflow) changed `initRtsFlagsDefaults` to enable stats collection by default. It's not entirely clear why, but I suspect it was a mistake. DemiMarie, do you have any recollection of this? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 23 21:32:34 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 23 Jun 2017 21:32:34 -0000 Subject: [GHC] #13864: RTS Stats are recorded without -T In-Reply-To: <044.9df229b07a94d2f8126cf8d8d9d18c67@haskell.org> References: <044.9df229b07a94d2f8126cf8d8d9d18c67@haskell.org> Message-ID: <059.8a7bb8d42d9c5f2de020190fb7fbd781@haskell.org> #13864: RTS Stats are recorded without -T -------------------------------------+------------------------------------- Reporter: glguy | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.2.1 Component: Runtime System | Version: 8.2.1-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): Ahhh, indeed this was intentional as the patch requires `stats.allocated_bytes`. However, I'm not sure I agree with how we went about this. If stat collection is now really mandatory then either we should remove the ability to disable it or just make sure that we always collect the bits that we need. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 23 21:46:57 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 23 Jun 2017 21:46:57 -0000 Subject: [GHC] #13864: RTS Stats are recorded without -T In-Reply-To: <044.9df229b07a94d2f8126cf8d8d9d18c67@haskell.org> References: <044.9df229b07a94d2f8126cf8d8d9d18c67@haskell.org> Message-ID: <059.223f9b4d685b131681002214bd4c3541@haskell.org> #13864: RTS Stats are recorded without -T -------------------------------------+------------------------------------- Reporter: glguy | Owner: (none) Type: bug | Status: patch Priority: normal | Milestone: 8.2.1 Component: Runtime System | Version: 8.2.1-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3669 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => patch * differential: => Phab:D3669 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 23 22:31:56 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 23 Jun 2017 22:31:56 -0000 Subject: [GHC] #13870: Empty record construction for record-less constructor gives surprising runtime error (and surprisingly few warnings) Message-ID: <050.fc98e01b762a6c8eb62abc4b92b4d47b@haskell.org> #13870: Empty record construction for record-less constructor gives surprising runtime error (and surprisingly few warnings) -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Keywords: newcomer | Operating System: Unknown/Multiple Architecture: | Type of failure: Poor/confusing Unknown/Multiple | error message Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- The crux of this ticket is this sort of code: {{{#!hs module Main where f :: Maybe Int f = Just{} main :: IO () main = print f }}} {{{ $ runghc --ghc-arg=-Wall Bug.hs Just Bug.hs: Bug.hs:4:5-10: Missing field in record construction }}} Yikes. There are a couple of very surprising things happening here. First, the message `Missing field in record construction` is very misleading. After all, `Just` has no records! We really should give a more specific error which highlights this fact. (The fact that you can even use record construction syntax with a record- less constructor in the first place is a bit baffling, but the [https://www.haskell.org/onlinereport/haskell2010/haskellch3.html#x8-520003.15.2 language standard does allow it], so I suppose we have to live with this.) The second surprising bit is the fact that is program compiled with no warnings whatsoever. This is in contrast to, say, the `Identity` datatype, which has a record (`runIdentity`): {{{#!hs module Main where import Data.Functor.Identity f :: Identity Int f = Identity{} main :: IO () main = print f }}} {{{ $ runghc --ghc-arg=-Wall Bug.hs Bug.hs:6:5: warning: [-Wmissing-fields] • Fields of ‘Identity’ not initialised: runIdentity • In the expression: Identity {} In an equation for ‘f’: f = Identity {} Identity Bug.hs: Bug.hs:6:5-14: Missing field in record construction runIdentity }}} Here, GHC warned me that I was doing something stupid. GHC ought to be warning me with equivalent fervor when I use `Just{}`. The warning would obviously have to be tweaked a bit, since warning that `Fields of ‘Just’ not initialised` doesn't make any sense, but you get the idea. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 23 23:44:02 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 23 Jun 2017 23:44:02 -0000 Subject: [GHC] #13871: GHC panic in 8.2 only: typeIsTypeable(Coercion) Message-ID: <050.f1a0fc44d1ac315eabed1b0be5437302@haskell.org> #13871: GHC panic in 8.2 only: typeIsTypeable(Coercion) -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: high | Milestone: 8.2.1 Component: Compiler | Version: 8.2.1-rc2 (Type checker) | Keywords: TypeInType, | Operating System: Unknown/Multiple Typeable | Architecture: | Type of failure: Compile-time Unknown/Multiple | crash or panic Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- This code works fine in GHC 8.0.1 and 8.0.2: {{{#!hs {-# LANGUAGE ConstraintKinds #-} {-# LANGUAGE GADTs #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE TypeInType #-} {-# LANGUAGE TypeOperators #-} module Foo where import Data.Kind data Foo (a :: Type) (b :: Type) where MkFoo :: (a ~ Int, b ~ Char) => Foo a b data family Sing (a :: k) data SFoo (z :: Foo a b) where SMkFoo :: SFoo MkFoo }}} But in GHC 8.2 and HEAD, it panics: {{{ $ /opt/ghc/8.2.1/bin/ghci Bug.hs GHCi, version 8.2.0.20170622: http://www.haskell.org/ghc/ :? for help Loaded GHCi configuration from /home/rgscott/.ghci [1 of 1] Compiling Foo ( Bug.hs, interpreted ) ghc: panic! (the 'impossible' happened) (GHC version 8.2.0.20170622 for x86_64-unknown-linux): typeIsTypeable(Coercion) }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 23 23:44:29 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 23 Jun 2017 23:44:29 -0000 Subject: [GHC] #13861: Take more advantage of STG representation invariance (follows up #9291) In-Reply-To: <048.651e325a747e822318af666cede88e81@haskell.org> References: <048.651e325a747e822318af666cede88e81@haskell.org> Message-ID: <063.c8fd58c5cef0c4a636492d55d2018845@haskell.org> #13861: Take more advantage of STG representation invariance (follows up #9291) -------------------------------------+------------------------------------- Reporter: heisenbug | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by nomeata): * cc: nomeata (added) Comment: This could presumably easily be added to the STG CSE pass (#9291). Or at least that is roughly the right spot. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jun 24 02:08:47 2017 From: ghc-devs at haskell.org (GHC) Date: Sat, 24 Jun 2017 02:08:47 -0000 Subject: [GHC] #13871: GHC panic in 8.2 only: typeIsTypeable(Coercion) In-Reply-To: <050.f1a0fc44d1ac315eabed1b0be5437302@haskell.org> References: <050.f1a0fc44d1ac315eabed1b0be5437302@haskell.org> Message-ID: <065.7faf6c30f1efdb01e4338b5c4de7ef58@haskell.org> #13871: GHC panic in 8.2 only: typeIsTypeable(Coercion) -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: high | Milestone: 8.2.1 Component: Compiler (Type | Version: 8.2.1-rc2 checker) | Keywords: TypeInType, Resolution: | Typeable Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * cc: bgamari (added) Comment: Commit 8fa4bf9ab3f4ea4b208f4a43cc90857987e6d497 (Type-indexed Typeable) caused this. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jun 24 03:00:52 2017 From: ghc-devs at haskell.org (GHC) Date: Sat, 24 Jun 2017 03:00:52 -0000 Subject: [GHC] #13871: GHC panic in 8.2 only: typeIsTypeable(Coercion) In-Reply-To: <050.f1a0fc44d1ac315eabed1b0be5437302@haskell.org> References: <050.f1a0fc44d1ac315eabed1b0be5437302@haskell.org> Message-ID: <065.7829365ea3e05048b21a5598d766d9f6@haskell.org> #13871: GHC panic in 8.2 only: typeIsTypeable(Coercion) -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: bgamari Type: bug | Status: new Priority: high | Milestone: 8.2.1 Component: Compiler (Type | Version: 8.2.1-rc2 checker) | Keywords: TypeInType, Resolution: | Typeable Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Compile-time | Test Case: crash or panic | typecheck/should_compile/T13871 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * testcase: => typecheck/should_compile/T13871 * owner: (none) => bgamari Comment: Oh dear, yes, I was slightly worried about issues like this. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jun 24 03:03:39 2017 From: ghc-devs at haskell.org (GHC) Date: Sat, 24 Jun 2017 03:03:39 -0000 Subject: [GHC] #13866: -g doesn't work with -pgma=clang++ In-Reply-To: <046.0cc5ec25fa742bf402aa06da26adeede@haskell.org> References: <046.0cc5ec25fa742bf402aa06da26adeede@haskell.org> Message-ID: <061.f497e06308d7d3a56fa3cd65ba57e369@haskell.org> #13866: -g doesn't work with -pgma=clang++ -------------------------------------+------------------------------------- Reporter: niteria | Owner: (none) Type: bug | Status: patch Priority: normal | Milestone: Component: Compiler | Version: 8.3 Resolution: | Keywords: Operating System: Linux | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3671, Wiki Page: | Phab:D3672 -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => patch * differential: => Phab:D3671, Phab:D3672 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jun 24 03:38:56 2017 From: ghc-devs at haskell.org (GHC) Date: Sat, 24 Jun 2017 03:38:56 -0000 Subject: [GHC] #13871: GHC panic in 8.2 only: typeIsTypeable(Coercion) In-Reply-To: <050.f1a0fc44d1ac315eabed1b0be5437302@haskell.org> References: <050.f1a0fc44d1ac315eabed1b0be5437302@haskell.org> Message-ID: <065.f733c5c05bd36081c4ba87329bb27344@haskell.org> #13871: GHC panic in 8.2 only: typeIsTypeable(Coercion) -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: bgamari Type: bug | Status: patch Priority: high | Milestone: 8.2.1 Component: Compiler (Type | Version: 8.2.1-rc2 checker) | Keywords: TypeInType, Resolution: | Typeable Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Compile-time | Test Case: crash or panic | typecheck/should_compile/T13871 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3671, Wiki Page: | Phab:D3672 -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => patch * differential: => Phab:D3671, Phab:D3672 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jun 24 03:39:53 2017 From: ghc-devs at haskell.org (GHC) Date: Sat, 24 Jun 2017 03:39:53 -0000 Subject: [GHC] #13866: -g doesn't work with -pgma=clang++ In-Reply-To: <046.0cc5ec25fa742bf402aa06da26adeede@haskell.org> References: <046.0cc5ec25fa742bf402aa06da26adeede@haskell.org> Message-ID: <061.c5c2529b8b9b42bec27754989e4c34cb@haskell.org> #13866: -g doesn't work with -pgma=clang++ ---------------------------------+---------------------------------------- Reporter: niteria | Owner: (none) Type: bug | Status: patch Priority: normal | Milestone: 8.2.1 Component: Compiler | Version: 8.3 Resolution: | Keywords: Operating System: Linux | Architecture: Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3667 Wiki Page: | ---------------------------------+---------------------------------------- Changes (by bgamari): * differential: Phab:D3671, Phab:D3672 => Phab:D3667 * milestone: => 8.2.1 Comment: Whoops, wrong Differential. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jun 24 03:58:45 2017 From: ghc-devs at haskell.org (GHC) Date: Sat, 24 Jun 2017 03:58:45 -0000 Subject: [GHC] #13810: Gold linker fails In-Reply-To: <045.174b108f34b20d346eba46d31b44114b@haskell.org> References: <045.174b108f34b20d346eba46d31b44114b@haskell.org> Message-ID: <060.31bf63d83c230244b7863f00331b7a28@haskell.org> #13810: Gold linker fails ---------------------------------+---------------------------------------- Reporter: ksaric | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: linker Operating System: Linux | Architecture: Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | ---------------------------------+---------------------------------------- Comment (by bgamari): I'm looking at the example described in the ticket summary: The issue here is that the library component was registered with (quoting `ghc-pkg dump`), {{{ ld-options: -fuse-ld=gold }}} Consequently, when we go to link the executable GHC will add this flag to its usual link flags, the latter of which assume that we are using BFD `ld`. Frankly, I don't see any better way to handle this beyond just teaching GHC to use `ld` when possible. I'm working on this (see #13541) but unfortunately it isn't likely that this will make the already-terribly- late 8.2.1. We may be able to work it in to 8.2.2 if we hear very vocal support from users, however. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jun 24 03:59:36 2017 From: ghc-devs at haskell.org (GHC) Date: Sat, 24 Jun 2017 03:59:36 -0000 Subject: [GHC] #13541: Make it easier to use the gold linker In-Reply-To: <046.0b1321a637ed3292c60514e6510d2c09@haskell.org> References: <046.0b1321a637ed3292c60514e6510d2c09@haskell.org> Message-ID: <061.47b6af9a95b9cd6be04519707d99d842@haskell.org> #13541: Make it easier to use the gold linker -------------------------------------+------------------------------------- Reporter: bgamari | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #13810 | Differential Rev(s): Phab:D3449 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * differential: => Phab:D3449 * related: => #13810 Comment: #13810 demonstrates the terrible brittleness of the current state of affairs, where we rely on users to explicitly set their choice of linker. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jun 24 12:59:37 2017 From: ghc-devs at haskell.org (GHC) Date: Sat, 24 Jun 2017 12:59:37 -0000 Subject: [GHC] #13810: Gold linker fails In-Reply-To: <045.174b108f34b20d346eba46d31b44114b@haskell.org> References: <045.174b108f34b20d346eba46d31b44114b@haskell.org> Message-ID: <060.4d9dcaf13385440a53297e80bd22074a@haskell.org> #13810: Gold linker fails ---------------------------------+---------------------------------------- Reporter: ksaric | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: linker Operating System: Linux | Architecture: Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | ---------------------------------+---------------------------------------- Comment (by nh2): Replying to [comment:8 bgamari]: > beyond just teaching GHC to use `ld` when possible Do you mean `gold`? > Consequently, when we go to link the executable GHC will add this flag to its usual link flags, the latter of which assume that we are using BFD ld. I don't quite understand this. Isn't the key problem here that the concept of the "ld program" and the "ld-options" are unhealthily mixed up? It seems to me that if one could explicitly distinguish "I want this linker" and "I want these ld-flags", the problem wouldn't exist, because then the choice of linker would not be propagated through `ld-options`. In other words, isn't the problem here that we're linking through the compiler (e.g. `gcc`) instead of the actual linker binary? Because otherwise we'd not even be using the `-fuse-ld` flag. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jun 24 13:01:33 2017 From: ghc-devs at haskell.org (GHC) Date: Sat, 24 Jun 2017 13:01:33 -0000 Subject: [GHC] #13810: Gold linker fails In-Reply-To: <045.174b108f34b20d346eba46d31b44114b@haskell.org> References: <045.174b108f34b20d346eba46d31b44114b@haskell.org> Message-ID: <060.1aa40d5f65e5c44774f753b76bcd92c0@haskell.org> #13810: Gold linker fails ---------------------------------+---------------------------------------- Reporter: ksaric | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: linker Operating System: Linux | Architecture: Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | ---------------------------------+---------------------------------------- Comment (by nh2): (Another workaround might be to make ghc ignore the `-fuse-ld` flag as a flag that can traverse `ld-options` through `build-depends`, but that option seems more hacky than linking directly with a linker executable, if that is possible.) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jun 24 14:42:17 2017 From: ghc-devs at haskell.org (GHC) Date: Sat, 24 Jun 2017 14:42:17 -0000 Subject: [GHC] #13810: Gold linker fails In-Reply-To: <045.174b108f34b20d346eba46d31b44114b@haskell.org> References: <045.174b108f34b20d346eba46d31b44114b@haskell.org> Message-ID: <060.2ee16393e8cbc5bd49624bf53aa7a6f9@haskell.org> #13810: Gold linker fails ---------------------------------+---------------------------------------- Reporter: ksaric | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: linker Operating System: Linux | Architecture: Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | ---------------------------------+---------------------------------------- Comment (by bgamari): > Do you mean gold? Whoops, yes. > I don't quite understand this. Isn't the key problem here that the concept of the "ld program" and the "ld-options" are unhealthily mixed up? > > In other words, isn't the problem here that we're linking through the compiler (e.g. `gcc`) instead of the actual linker binary? Because otherwise we'd not even be using the `-fuse-ld` flag. I've played around with the idea of involing `ld` ourselves and have concluded that it's almost certainly going to hurt more than it helps. Linking tends to be terribly platform specific and rather difficult to get right (see also: `gcc -dumpspecs`). Moreover, linkers on many platforms tend to be, shall we say, quirky. I don't see us being able to robustly implement the logic necessary to drive the linker as well as `gcc`. Keep in mind that GHC is not only responsible for linking Haskell; we are often asked to link against native code, some of which may require peculiar linking behavior (e.g. one of those many rules seen in `gcc -dumpspecs`). This isn't to say that `gcc`'s abstraction over linking is quite perfect; far from it. However, it's IMHO much better than having to dive into the muck ourselves. Moreover, I don't think thinking ourselves would necessarily help the crux of this problem: the user essentially gave us conflicting linking options. Really, the user shouldn't have to give us *any* linker options in this case; `ghc` should just handle linker choice for you. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jun 24 16:06:17 2017 From: ghc-devs at haskell.org (GHC) Date: Sat, 24 Jun 2017 16:06:17 -0000 Subject: [GHC] #13872: Strange Typeable error message involving TypeInType Message-ID: <050.3b6072a1389bdaa345d0cbeac9135be1@haskell.org> #13872: Strange Typeable error message involving TypeInType -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 (Type checker) | Keywords: TypeInType, | Operating System: Unknown/Multiple Typeable | Architecture: | Type of failure: Poor/confusing Unknown/Multiple | error message Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- I originally discovered this when tinkering with #13871. This program: {{{#!hs {-# LANGUAGE ConstraintKinds #-} {-# LANGUAGE GADTs #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE TypeInType #-} {-# LANGUAGE TypeOperators #-} module Foo where import Data.Kind import Data.Typeable data Foo (a :: Type) (b :: Type) where MkFoo :: (a ~ Int, b ~ Char) => Foo a b data family Sing (a :: k) data SFoo (z :: Foo a b) where SMkFoo :: SFoo MkFoo f :: String f = show $ typeOf SMkFoo }}} Fails in GHC 8.0.1, 8.0.2, and 8.2 (after applying Phab:D3671) with a rather unsightly error message: {{{ GHCi, version 8.3.20170624: http://www.haskell.org/ghc/ :? for help Loaded GHCi configuration from /home/rgscott/.ghci [1 of 1] Compiling Foo ( Foo.hs, interpreted ) Foo.hs:19:12: error: • No instance for (Typeable <>) arising from a use of ‘typeOf’ • In the second argument of ‘($)’, namely ‘typeOf SMkFoo’ In the expression: show $ typeOf SMkFoo In an equation for ‘f’: f = show $ typeOf SMkFoo | 19 | f = show $ typeOf SMkFoo | ^^^^^^^^^^^^^ }}} I'm not sure what this mysterious `<>` is, but I'm pretty sure it shouldn't be making an appearance here. (See also #13780, where `<>` also makes a surprise guest appearance.) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jun 24 17:00:57 2017 From: ghc-devs at haskell.org (GHC) Date: Sat, 24 Jun 2017 17:00:57 -0000 Subject: [GHC] #13747: Can't use 'instance' keyword in associated type family instance In-Reply-To: <042.cfa21cd9140248a25075b778770d0326@haskell.org> References: <042.cfa21cd9140248a25075b778770d0326@haskell.org> Message-ID: <057.b5a432144d92b1aee8d2ca2072c3ac05@haskell.org> #13747: Can't use 'instance' keyword in associated type family instance -------------------------------------+------------------------------------- Reporter: nh2 | Owner: erdeszt Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.2 Resolution: | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple error/warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3673 Wiki Page: | -------------------------------------+------------------------------------- Changes (by erdeszt): * owner: (none) => erdeszt * differential: => Phab:D3673 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jun 24 17:55:24 2017 From: ghc-devs at haskell.org (GHC) Date: Sat, 24 Jun 2017 17:55:24 -0000 Subject: [GHC] #13848: Unexpected order of variable quantification with GADT constructor In-Reply-To: <050.1bdc037c5d3daf9f53281904769def22@haskell.org> References: <050.1bdc037c5d3daf9f53281904769def22@haskell.org> Message-ID: <065.ed8d127306869c5fd5d05930767388ac@haskell.org> #13848: Unexpected order of variable quantification with GADT constructor -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.1 checker) | Keywords: Resolution: | TypeApplications Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): I don't think it's going to be that simple. If you look at the implementation of `mkDataConRep`, you'll notice that it figures out the type of the `wrap_id` like this: {{{#!hs wrap_ty = dataConUserType data_con }}} So obviously we don't want to change `dataConUserType`'s implementation to use `idType wrap_id`, since that would be a circular definition. > We should ensure that the wrapper type reflects exactly the type the user wrote including type variable order Sure, but that's easier said than done. The only info you have in `mkDataConId` to determine the wrapper type is the `DataCon` itself, and at that point, the type variables have already been carved up into the universal and existential ones, with no way to recover the original order. So I don't see any way to make this work without having a separate `dcOrigTyVars` fields, as proposed in comment:2. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jun 24 19:37:18 2017 From: ghc-devs at haskell.org (GHC) Date: Sat, 24 Jun 2017 19:37:18 -0000 Subject: [GHC] #13541: Make it easier to use the gold linker In-Reply-To: <046.0b1321a637ed3292c60514e6510d2c09@haskell.org> References: <046.0b1321a637ed3292c60514e6510d2c09@haskell.org> Message-ID: <061.e92e1745b46db5150e2c27daa6c06774@haskell.org> #13541: Make it easier to use the gold linker -------------------------------------+------------------------------------- Reporter: bgamari | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #13810 | Differential Rev(s): Phab:D3449 Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): I've updated Phab:D3449 to reflect my current thinking on this. Namely, we provide a `configure` flag that indicates that the user doesn't mind if GHC overrides the system's default linker. If this flag is passed, we use either `gold` or `lld`, if available. The user can explicitly request one or the other by passing the `LD=...` variable to `configure`. Does this seem reasonable? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jun 24 20:31:09 2017 From: ghc-devs at haskell.org (GHC) Date: Sat, 24 Jun 2017 20:31:09 -0000 Subject: [GHC] #13872: Strange Typeable error message involving TypeInType In-Reply-To: <050.3b6072a1389bdaa345d0cbeac9135be1@haskell.org> References: <050.3b6072a1389bdaa345d0cbeac9135be1@haskell.org> Message-ID: <065.eb9a8e3224ca63f627daa2ea88c14e7d@haskell.org> #13872: Strange Typeable error message involving TypeInType -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.1 checker) | Keywords: TypeInType, Resolution: | Typeable Operating System: Unknown/Multiple | Architecture: Type of failure: Poor/confusing | Unknown/Multiple error message | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): `<>` is what the type pretty-printer calls `Coercion` types. AFAICT it's not entirely trivial making this `Typeable`, since the constructor's actual kind does indeed contain a coercion. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jun 24 20:32:53 2017 From: ghc-devs at haskell.org (GHC) Date: Sat, 24 Jun 2017 20:32:53 -0000 Subject: [GHC] #13872: Strange Typeable error message involving TypeInType In-Reply-To: <050.3b6072a1389bdaa345d0cbeac9135be1@haskell.org> References: <050.3b6072a1389bdaa345d0cbeac9135be1@haskell.org> Message-ID: <065.76dbaf95aefe9e6df0269514e1923dd9@haskell.org> #13872: Strange Typeable error message involving TypeInType -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.1 checker) | Keywords: TypeInType, Resolution: | Typeable Operating System: Unknown/Multiple | Architecture: Type of failure: Poor/confusing | Unknown/Multiple error message | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): To be clear: I'm not requesting that this datatype be an instance of `Typeable`, only that the error message be improved. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jun 24 20:37:34 2017 From: ghc-devs at haskell.org (GHC) Date: Sat, 24 Jun 2017 20:37:34 -0000 Subject: [GHC] #13872: Strange Typeable error message involving TypeInType In-Reply-To: <050.3b6072a1389bdaa345d0cbeac9135be1@haskell.org> References: <050.3b6072a1389bdaa345d0cbeac9135be1@haskell.org> Message-ID: <065.1c1453dbfa5536ccbfd5e9eb9a1c03d1@haskell.org> #13872: Strange Typeable error message involving TypeInType -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.1 checker) | Keywords: TypeInType, Resolution: | Typeable Operating System: Unknown/Multiple | Architecture: Type of failure: Poor/confusing | Unknown/Multiple error message | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): Ahhh, yes that is quite a reasonable request. Indeed it is quite poor. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jun 24 21:30:21 2017 From: ghc-devs at haskell.org (GHC) Date: Sat, 24 Jun 2017 21:30:21 -0000 Subject: [GHC] #13541: Make it easier to use the gold linker In-Reply-To: <046.0b1321a637ed3292c60514e6510d2c09@haskell.org> References: <046.0b1321a637ed3292c60514e6510d2c09@haskell.org> Message-ID: <061.f0d7708879179f2d89add2190fa5ec9b@haskell.org> #13541: Make it easier to use the gold linker -------------------------------------+------------------------------------- Reporter: bgamari | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #13810 | Differential Rev(s): Phab:D3449 Wiki Page: | -------------------------------------+------------------------------------- Comment (by nh2): > The user can explicitly request one or the other by passing the LD=... variable to configure. @bgamari: To clarify, will GHC still at run-time detect which linker is available, and can the user still at run-time tell GHC which linker to use? At configure time, gold may not be installed, or it may be uninstalled afterwards, or the user maybe be using a bindist but for some reasons wants to force GHC to use `ld` or `gold` (for example, if `gold` doesn't work for them for some reason). -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Jun 25 00:00:28 2017 From: ghc-devs at haskell.org (GHC) Date: Sun, 25 Jun 2017 00:00:28 -0000 Subject: [GHC] #13873: Adding a SPECIALIZE at a callsite in Main.hs is causing a regression Message-ID: <048.468ab4797659afca428d5d90c27d98b1@haskell.org> #13873: Adding a SPECIALIZE at a callsite in Main.hs is causing a regression -------------------------------------+------------------------------------- Reporter: jberryman | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.1-rc2 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- Github user jmoy documents an issue with lack of specialization happening for INLINABLE functions in GHC 8.0 here: https://github.com/jmoy/testing- specialize . Testing on 8.2.1 it seems that specialization happened (although I didn't verify this in the core) as the result was 10x faster. But the odd thing to me was uncommenting the `SPECIALIZE` pragma at the callsite actually resulted in a significant regression: https://github.com/jmoy/testing-specialize/issues/1#issuecomment-310868360 Maybe GHC is choosing the worse manual partial specialization for some reason. I'm sorry I can't produce a better ticket for this at the moment. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Jun 25 00:01:19 2017 From: ghc-devs at haskell.org (GHC) Date: Sun, 25 Jun 2017 00:01:19 -0000 Subject: [GHC] #13376: GHC fails to specialize a pair of polymorphic INLINABLE functions In-Reply-To: <048.eb8da202bb2996fcfeb70c826114f591@haskell.org> References: <048.eb8da202bb2996fcfeb70c826114f591@haskell.org> Message-ID: <063.89b198052344a2466ef511811ada4c18@haskell.org> #13376: GHC fails to specialize a pair of polymorphic INLINABLE functions -------------------------------------+------------------------------------- Reporter: jberryman | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.2.1 Component: Compiler | Version: 8.0.1 Resolution: fixed | Keywords: Inlining Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: #8668, #5835, | Differential Rev(s): #12791 | Wiki Page: | -------------------------------------+------------------------------------- Comment (by jberryman): Just a note that I verified the example I posted here is fixed in 8.2, as well as jmoy's example I linked to in the first paragraph of my report. However for the latter I encountered what I thought was a weird issue which I don't have time to look into further right now: https://ghc.haskell.org/trac/ghc/ticket/13873 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Jun 25 00:45:20 2017 From: ghc-devs at haskell.org (GHC) Date: Sun, 25 Jun 2017 00:45:20 -0000 Subject: =?utf-8?b?UmU6IFtHSENdICMxMzYxNTogTm9uZGV0ZXJtaW5pc20gaW4g4oCY?= =?utf-8?q?pure=E2=80=99_function_w/_parallel_evaluation_=26_memo?= =?utf-8?q?_combinators?= In-Reply-To: <044.57733831351687fff6258688df1f42f7@haskell.org> References: <044.57733831351687fff6258688df1f42f7@haskell.org> Message-ID: <059.871c73ed662b99b3e028534e346f71ce@haskell.org> #13615: Nondeterminism in ‘pure’ function w/ parallel evaluation & memo combinators -------------------------------------+------------------------------------- Reporter: pacak | Owner: bgamari Type: bug | Status: new Priority: highest | Milestone: 8.2.1 Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): I have confirmed that we indeed hit the codepath in `raiseAsync` responsible for updating the thunk under evaluation. I believe this fills the final question in comment:36. To recap, what is happening is the following, 1. Thread A enters a `fromListWith` closure and begins folding over the insertions 2. At some point during this fold we need to garbage collect (usually due to a stack overflow, judging from the eventlog); the garbage collector construct an `AP_STACK` closure capturing the state of Thread A, including the partially-finished `fromListWith` computation. The `fromListWith` thunk is updated to point to this `AP_STACK`. 3. Garbage collection commences and finishes, evaluation resumes 4. At some point Thread A is resumed, entering the previously saved `AP_STACK` computation which we prepared in step (2); we are blackholing lazily so no update to the `AP_STACK` closure is made 5. At some later point Thread B tries to force the same `AP_STACK` computation; finding that it's not blackholed, it enters We now have two mutator threads performing evaluation on the same, effectful computation with shared, mutable state. My first intuition says that the easiest way to avoid this would be to unconditionally eagerly blackhole `AP_STACK`s. I believe this can be done straightforwardly, {{{#!diff diff --git a/rts/Apply.cmm b/rts/Apply.cmm index f14bb8f331..a35b41e5b0 100644 --- a/rts/Apply.cmm +++ b/rts/Apply.cmm @@ -464,6 +464,16 @@ INFO_TABLE(stg_AP_STACK,/*special layout*/0,0,AP_STACK,"AP_STACK","AP_STACK") Words = StgAP_STACK_size(ap); + W_ old_info; + (old_info) = prim %cmpxchgW(ap, stg_AP_STACK_info, stg_WHITEHOLE_info); + if (old_info != stg_AP_STACK_info) { + /* someone else beat us to it */ + jump ENTRY_LBL(stg_WHITEHOLE) (ap); + } + StgInd_indirectee(ap) = CurrentTSO; + W_[ap] = stg_EAGER_BLACKHOLE_info; + /* * Check for stack overflow. IMPORTANT: use a _ENTER check here, * because if the check fails, we might end up blackholing this very }}} However, in doing this I'm seeing `<>` in the testcase. I haven't yet worked out why. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Jun 25 02:11:38 2017 From: ghc-devs at haskell.org (GHC) Date: Sun, 25 Jun 2017 02:11:38 -0000 Subject: [GHC] #13541: Make it easier to use the gold linker In-Reply-To: <046.0b1321a637ed3292c60514e6510d2c09@haskell.org> References: <046.0b1321a637ed3292c60514e6510d2c09@haskell.org> Message-ID: <061.c90ebba9df1d628449be4eb98dac6b56@haskell.org> #13541: Make it easier to use the gold linker -------------------------------------+------------------------------------- Reporter: bgamari | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #13810 | Differential Rev(s): Phab:D3449 Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): The diff doesn't touch the runtime linker-detection logic. It also doesn't provide a way for the user to override the linker choice, but this could be fixed. However, I do wish we could drop the runtime probing at some point. Currently we start `gcc -v` and `ld -v` on every single GHC compilation. On platforms like Windows this can really add up. Even on Linux, where process spawning is relatively fast, it's probably 5 to 10 milliseconds per execution. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Jun 25 02:18:12 2017 From: ghc-devs at haskell.org (GHC) Date: Sun, 25 Jun 2017 02:18:12 -0000 Subject: [GHC] #13873: Adding a SPECIALIZE at a callsite in Main.hs is causing a regression In-Reply-To: <048.468ab4797659afca428d5d90c27d98b1@haskell.org> References: <048.468ab4797659afca428d5d90c27d98b1@haskell.org> Message-ID: <063.b651a02a88fffec1310185bb9b17c584@haskell.org> #13873: Adding a SPECIALIZE at a callsite in Main.hs is causing a regression -------------------------------------+------------------------------------- Reporter: jberryman | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.2.2 Component: Compiler | Version: 8.2.1-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * failure: None/Unknown => Runtime performance bug * milestone: => 8.2.2 Comment: Quite suspicious indeed. I'll have a look. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Jun 25 05:20:09 2017 From: ghc-devs at haskell.org (GHC) Date: Sun, 25 Jun 2017 05:20:09 -0000 Subject: [GHC] #8177: Roles for type families In-Reply-To: <046.bd13b30db1cfd3d4628960446a01267b@haskell.org> References: <046.bd13b30db1cfd3d4628960446a01267b@haskell.org> Message-ID: <061.d854c27f21f1ac8b504939f2fbac35c2@haskell.org> #8177: Roles for type families -------------------------------------+------------------------------------- Reporter: simonpj | Owner: goldfire Type: bug | Status: new Priority: normal | Milestone: ⊥ Component: Compiler | Version: 7.6.3 Resolution: | Keywords: TypeFamilies Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3662 Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): Indeed, I will readily admit that I'm mostly parking this Diff here for Richard's sake (when he gets a chance to look at it). However, since you asked politely, I wrote up an (informal) specification of how I envision this would work [https://ghc.haskell.org/trac/ghc/wiki/Roles#Proposal:rolesfortypefamilies here], based on the conversations I've had with Richard about this topic, as well as the commentary in this ticket. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Jun 25 12:23:21 2017 From: ghc-devs at haskell.org (GHC) Date: Sun, 25 Jun 2017 12:23:21 -0000 Subject: [GHC] #13874: GHC panic related to hybrid-vectors Message-ID: <045.be59b903bf6150ed0eb712286edb3741@haskell.org> #13874: GHC panic related to hybrid-vectors -------------------------------------+------------------------------------- Reporter: ocramz | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Keywords: | Operating System: MacOS X Architecture: | Type of failure: Compile-time Unknown/Multiple | crash or panic Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- The following module makes GHC 8.0.1 panic when the `fromList` declaration is uncommented: {{{#!hs import qualified Data.Vector.Hybrid as VH import qualified Data.Vector.Unboxed as VU import qualified Data.Vector as V data SHVector a = SHV {-# UNPACK #-} !Int !(VH.Vector VU.Vector V.Vector (Int, a)) deriving (Eq) fromList :: Int -> [(Int, a)] -> SHVector a fromList n ll = SHV n (VH.fromList ll) }}} Crash message follows: {{{#!hs ghc: panic! (the 'impossible' happened) (GHC version 8.0.1 for x86_64-apple-darwin): Template variable unbound in rewrite rule Variable: sc_shyr Rule "SC:$j0" Rule bndrs: [sc_shyr, sc_shys, sc_shyt, sg_shyu, sc_shyq] LHS args: [sc_shyq, (MV @ (Mutable Vector) @ (Mutable Vector) @ (PrimState (ST RealWorld)) @ (Int, a_aeG1) @ Int @ a_aeG1 @~ (<(Int, a_aeG1)>_N :: ((Int, a_aeG1) :: *) ~# ((Int, a_aeG1) :: *)) sc_shys sc_shyt) `cast` (sg_shyu :: (MVector (Mutable Vector) (Mutable Vector) (PrimState (ST RealWorld)) (Int, a_aeG1) :: *) ~R# (Mutable (Vector Vector Vector) (PrimState (ST RealWorld)) (Int, a_aeG1) :: *))] Actual args: [sc_shyk, wild_ahdD `cast` (Sub (Sym (D:R:MutableVector[0] _N _N)) _N <(Int, a_aeG1)>_N :: (MVector (Mutable Vector) (Mutable Vector) (PrimState (ST RealWorld)) (Int, a_aeG1) :: *) ~R# (Mutable (Vector Vector Vector) (PrimState (ST RealWorld)) (Int, a_aeG1) :: *))] }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Jun 25 12:28:10 2017 From: ghc-devs at haskell.org (GHC) Date: Sun, 25 Jun 2017 12:28:10 -0000 Subject: [GHC] #13874: GHC panic related to hybrid-vectors In-Reply-To: <045.be59b903bf6150ed0eb712286edb3741@haskell.org> References: <045.be59b903bf6150ed0eb712286edb3741@haskell.org> Message-ID: <060.a2acfd1d0aba6aec5983d5380d38ff83@haskell.org> #13874: GHC panic related to hybrid-vectors -------------------------------------+------------------------------------- Reporter: ocramz | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: MacOS X | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by ocramz): I just understood this might be related to https://ghc.haskell.org/trac/ghc/ticket/13410 ; can anyone confirm? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Jun 25 13:07:10 2017 From: ghc-devs at haskell.org (GHC) Date: Sun, 25 Jun 2017 13:07:10 -0000 Subject: [GHC] #8177: Roles for type families In-Reply-To: <046.bd13b30db1cfd3d4628960446a01267b@haskell.org> References: <046.bd13b30db1cfd3d4628960446a01267b@haskell.org> Message-ID: <061.589cbe1674d733325fbbc2129ea75200@haskell.org> #8177: Roles for type families -------------------------------------+------------------------------------- Reporter: simonpj | Owner: goldfire Type: bug | Status: new Priority: normal | Milestone: ⊥ Component: Compiler | Version: 7.6.3 Resolution: | Keywords: TypeFamilies Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3662 Wiki Page: | -------------------------------------+------------------------------------- Comment (by goldfire): I've commented on the wiki page (the specification) and on the diff. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Jun 25 15:05:06 2017 From: ghc-devs at haskell.org (GHC) Date: Sun, 25 Jun 2017 15:05:06 -0000 Subject: [GHC] #13874: GHC panic related to hybrid-vectors In-Reply-To: <045.be59b903bf6150ed0eb712286edb3741@haskell.org> References: <045.be59b903bf6150ed0eb712286edb3741@haskell.org> Message-ID: <060.6871daab563fab0437441435825599ae@haskell.org> #13874: GHC panic related to hybrid-vectors -------------------------------------+------------------------------------- Reporter: ocramz | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: duplicate | Keywords: Operating System: MacOS X | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: #13410 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * status: new => closed * resolution: => duplicate * related: => #13410 Comment: I believe this is in fact a duplicate of #13410. FWIW, I can't reproduce this bug in GHC 8.2.1. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Jun 25 15:19:36 2017 From: ghc-devs at haskell.org (GHC) Date: Sun, 25 Jun 2017 15:19:36 -0000 Subject: [GHC] #8177: Roles for type families In-Reply-To: <046.bd13b30db1cfd3d4628960446a01267b@haskell.org> References: <046.bd13b30db1cfd3d4628960446a01267b@haskell.org> Message-ID: <061.f5894d3b1387c0ec38d7e6d20be1e1e1@haskell.org> #8177: Roles for type families -------------------------------------+------------------------------------- Reporter: simonpj | Owner: goldfire Type: bug | Status: new Priority: normal | Milestone: ⊥ Component: Compiler | Version: 7.6.3 Resolution: | Keywords: TypeFamilies Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3662 Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): Thanks for replying, Richard! I'll respond to your comments here (since I don't like using wiki pages as a medium of conversation). > **RAE**: "feels"? Let's prove it! End **RAE** Hoo boy, I was afraid you were going to demand a proof. I certainly don't have one at the moment. > **RAE**: There is a difference between roles for data families and data instances. And both might usefully have role annotations. For example: > > {{{#!hs > data family DF a b > type role DF nominal representational > > data instance DF Int b = MkDFInt b > -- NB: No scrutinizing the second parameter. > -- Also, b is not used in a nominal context > > data instance DF [c] b = MkDFList c b > type role DF [nominal] representational > > data instance DF (Maybe d) b = MkDFMaybe d b > type role DF (Maybe representational) representational > }}} > > With this, we have `Coercible (DF (Maybe Age) Int) (DF (Maybe Int) Age)` but not `Coercible (DF [Age] Int) (DF [Int] Age)`. Ah, I think there's a bit of confusion regarding the extent of this design. To be clear, I am not proposing that we give users the power to specify roles the type variables in each //equation//, only the type variables of the parent type family itself. This is because: 1. As your example hints at, we'd need to invent a new syntax for role annotations that match on particular types, and I don't feel anywhere near motivated enough to implement that. 2. The current implementation of role inference does not lend itself well to this design. GHC assigns roles by using a map from `TyCon` names to roles, but type family equations have neither `TyCon`s nor any kind of unique identifier from which we could look up its roles after inference. 3. This kind of power isn't necessary for the kind of stuff I'd want to do anyways. All I really care about is that the second parameter is designated as `representational`. I don't really want the ability to `coerce` between `DF (Maybe Age) Int` and `DF (Maybe Age) Int`. So in your above example: {{{#!hs data family DF a b type role DF nominal representational data instance DF [c] b = MkDFList c b data instance DF (Maybe d) b = MkDFMaybe d b }}} I would propose that the tyvars in any type pattern which saturates `a` should inherit the role of `a`, so `c` and `d` would get role `nominal` in their respective equations. It's not as permissive as it //could// be, but for reasons that I explained above (and I'll make a note of this in the wiki). > I'm a bit worried about problems with what happens if a type constructor that appears as part of a type pattern for an instance is actually a newtype with a role annotation -- could we be breaking soundness with this? Need to think harder. I don't understand this point. > **RAE**: This works well for closed type families, but is ineffective with open type/data families (associated or not). I propose that open families default to nominal roles. This is quite like how open families' type variables default to kind Type. Edit: I see this addressed below, but the opening paragraph for this section mentions inference for open families. **End RAE** Yep, that's my bad. I'll update the intro so as not to mislead readers. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Jun 25 16:22:34 2017 From: ghc-devs at haskell.org (GHC) Date: Sun, 25 Jun 2017 16:22:34 -0000 Subject: [GHC] #8177: Roles for type families In-Reply-To: <046.bd13b30db1cfd3d4628960446a01267b@haskell.org> References: <046.bd13b30db1cfd3d4628960446a01267b@haskell.org> Message-ID: <061.8db9b747684894c87dfa7d10e455741f@haskell.org> #8177: Roles for type families -------------------------------------+------------------------------------- Reporter: simonpj | Owner: goldfire Type: bug | Status: new Priority: normal | Milestone: ⊥ Component: Compiler | Version: 7.6.3 Resolution: | Keywords: TypeFamilies Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3662 Wiki Page: | -------------------------------------+------------------------------------- Comment (by goldfire): Replying to [comment:39 RyanGlScott]: > Hoo boy, I was afraid you were going to demand a proof. I certainly don't have one at the moment. "Demand"? No. But it would be nice if the design could at least update the various relevant judgments in the "Safe coercions" paper (use the JFP version). It shouldn't be terribly much work, and it's likely that the process of doing so will reveal any glaring problems. And once you have the updated judgments, it's also not terribly hard to follow along the JFP proof and see what lemmas have to be updated. I'm always daunted by having to revisit the type safety proof. But every time I go through the process, my brain feels nice, limber, and at peace. It's all very much like a good yoga session: it's hard to find the time to do it, it involves painful contortions, and yet you feel quite good at the end. > Ah, I think there's a bit of confusion regarding the extent of this design. To be clear, I am not proposing that we give users the power to specify roles the type variables in each //equation//, only the type variables of the parent type family itself. Note that instance-specific roles apply only to ''data'' families, not ''type'' families. > This is because: > > 1. As your example hints at, we'd need to invent a new syntax for role annotations that match on particular types, and I don't feel anywhere near motivated enough to implement that. And neither was I, as you'll see in my comment:5. > 2. The current implementation of role inference does not lend itself well to this design. GHC assigns roles by using a map from `TyCon` names to roles, but type family equations have neither `TyCon`s nor any kind of unique identifier from which we could look up its roles after inference. This isn't as bad as you say. Data family instances ''do'' have a `TyCon`. See the `DataFamilyInst` constructor of `FamInstEnv.FamFlavor`. > 3. This kind of power isn't necessary for the kind of stuff I'd want to do anyways. All I really care about is that the second parameter is designated as `representational`. I don't really want the ability to `coerce` between `DF (Maybe Age) Int` and `DF (Maybe Age) Int`. So perhaps you want just roles for ''type'' families for now, not ''data'' families. > > So in your above example: > > {{{#!hs > data family DF a b > type role DF nominal representational > data instance DF [c] b = MkDFList c b > data instance DF (Maybe d) b = MkDFMaybe d b > }}} > > I would propose that the tyvars in any type pattern which saturates `a` should inherit the role of `a`, so `c` and `d` would get role `nominal` in their respective equations. It's not as permissive as it //could// be, but for reasons that I explained above (and I'll make a note of this in the wiki). But any time a pattern introduces a new tyvar (that's not just a renaming of the tycon tyvar), then the "parent" tyvar's role is always nominal (because you're doing pattern matching). As you note, this is not as permissive as possible. But, I would argue that if you were as permissive as possible, then you'd have no way of making a fully-abstract data family instance. So your design is self-consistent. > > > I'm a bit worried about problems with what happens if a type constructor that appears as part of a type pattern for an instance is actually a newtype with a role annotation -- could we be breaking soundness with this? Need to think harder. > > I don't understand this point. I was worried about something like this: {{{#!hs newtype Inty a = MkInty Int type role Inty representational -- just because I can data family F a type role F nominal data instance F (Inty a) = MkF a type role F (Inty nominal) }}} Is this a good idea? I don't know. Keep in mind that data families are injective. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Jun 25 16:42:04 2017 From: ghc-devs at haskell.org (GHC) Date: Sun, 25 Jun 2017 16:42:04 -0000 Subject: [GHC] #8177: Roles for type families In-Reply-To: <046.bd13b30db1cfd3d4628960446a01267b@haskell.org> References: <046.bd13b30db1cfd3d4628960446a01267b@haskell.org> Message-ID: <061.eff3b933f7dfda02179638128a62ac5f@haskell.org> #8177: Roles for type families -------------------------------------+------------------------------------- Reporter: simonpj | Owner: goldfire Type: bug | Status: new Priority: normal | Milestone: ⊥ Component: Compiler | Version: 7.6.3 Resolution: | Keywords: TypeFamilies Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3662 Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): Replying to [comment:40 goldfire]: > I'm always daunted by having to revisit the type safety proof. It's doubly daunting for me because I wouldn't be //re//visiting the proof—I'd be trudging through it for the first time. :) Not to say that I'm not willing to do this at some point, but it will take me a significant amount of time to invest in understanding the terminology (keep in mind I'm far from an expert on the intricacies of System FC), not to mention figuring out how to typeset all of those crazy typing judgments in TeX. > So perhaps you want just roles for ''type'' families for now, not ''data'' families. Well, I //do// want to have roles for data families at some point (I started with closed type families since they're considerably easier to implement). I just don't want to worry about the additional baggage that per-data-instance role annotations would entail. > But any time a pattern introduces a new tyvar (that's not just a renaming of the tycon tyvar), then the "parent" tyvar's role is always nominal (because you're doing pattern matching). As you note, this is not as permissive as possible. But, I would argue that if you were as permissive as possible, then you'd have no way of making a fully-abstract data family instance. So your design is self-consistent. Absolutely. I'm fine with making `nominal` roles be overly restrictive, since it dodges thorny issues like data abstraction... > I was worried about something like this: > > {{{#!hs > newtype Inty a = MkInty Int > type role Inty representational -- just because I can > > data family F a > type role F nominal > > data instance F (Inty a) = MkF a > type role F (Inty nominal) > }}} > > Is this a good idea? I don't know. Keep in mind that data families are injective. ...and this sort of thing as well. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 26 03:00:03 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 26 Jun 2017 03:00:03 -0000 Subject: [GHC] #13875: ApplicativeDo desugaring is lazier than standard desugaring Message-ID: <045.2eda858359df0999208d04da5f95a1da@haskell.org> #13875: ApplicativeDo desugaring is lazier than standard desugaring -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.4.1 Component: Compiler | Version: 8.3 Keywords: ApplicativeDo | Operating System: Unknown/Multiple Architecture: | Type of failure: Other Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- Suppose I write {{{#!hs import Data.Maybe (isJust) bangy m = do (_,_) <- m return () main = print $ isJust (bangy (Just undefined)) }}} If I compile this with `ApplicativeDo`, it prints `True`. Otherwise, it throws an exception. The basic problem is that the (correct) `bangy` function ''requires'' a `Monad` constraint, but `ApplicativeDo` replaces it with a lazier function that can get by with `Functor`. I believe it should desugar correctly, and impose a `Monad` constraint here. To get the `Functor` constraint should require an explicit lazy pattern match: {{{#!hs bangy m = do ~(_,_) <- m return () }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 26 03:01:17 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 26 Jun 2017 03:01:17 -0000 Subject: [GHC] #13875: ApplicativeDo desugaring is lazier than standard desugaring In-Reply-To: <045.2eda858359df0999208d04da5f95a1da@haskell.org> References: <045.2eda858359df0999208d04da5f95a1da@haskell.org> Message-ID: <060.8af06a19c25a42d4d63ceabccea4293f@haskell.org> #13875: ApplicativeDo desugaring is lazier than standard desugaring -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.4.1 Component: Compiler | Version: 8.3 Resolution: | Keywords: ApplicativeDo Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Other | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by dfeuer): Note that the documentation indicates > Applicative do-notation desugaring preserves the original semantics, provided that the `Applicative` instance satisfies `<*> = ap` and `pure = return` (these are true of all the common monadic types). Thus, you can normally turn on `-XApplicativeDo` without fear of breaking your program. There is one pitfall to watch out for; see Things to watch out for. This is simply not true at the moment. The "Things to watch out for" section is unrelated. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 26 03:26:52 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 26 Jun 2017 03:26:52 -0000 Subject: [GHC] #13875: ApplicativeDo desugaring is lazier than standard desugaring In-Reply-To: <045.2eda858359df0999208d04da5f95a1da@haskell.org> References: <045.2eda858359df0999208d04da5f95a1da@haskell.org> Message-ID: <060.827a62abffa1c24149a57292882b476c@haskell.org> #13875: ApplicativeDo desugaring is lazier than standard desugaring -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: (none) Type: bug | Status: new Priority: high | Milestone: 8.2.1 Component: Compiler | Version: 8.3 Resolution: | Keywords: ApplicativeDo Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Other | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by dfeuer): * priority: normal => high * milestone: 8.4.1 => 8.2.1 Comment: I'm setting a milestone of 8.2.1 and high priority to at least ''document'' what the extension actually does right now. If the powers that be want to fix it, then we can set a milestone of 8.4 for the fix if necessary. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 26 04:20:36 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 26 Jun 2017 04:20:36 -0000 Subject: [GHC] #13739: very slow linking of executables with ld.bfd < 2.27 (was: Very slow linking of profiled executables) In-Reply-To: <043.2d2650cd128632597774b5afb6c7a225@haskell.org> References: <043.2d2650cd128632597774b5afb6c7a225@haskell.org> Message-ID: <058.14819dcf3da6f1b87416789091417baf@haskell.org> #13739: very slow linking of executables with ld.bfd < 2.27 -------------------------------------+------------------------------------- Reporter: duog | Owner: (none) Type: bug | Status: new Priority: high | Milestone: 8.2.1 Component: Compiler | Version: 8.2.1-rc2 Resolution: | Keywords: Operating System: Linux | Architecture: x86_64 Type of failure: Compile-time | (amd64) performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by duog): This problem rears its head in an ugly fasion while configuring packages that have custom setups: {{{ cabal unpack distributive-0.5.2 cd distributive-0.5.2 cabal sandbox init cabal install --only-dependencies time cabal configure }}} gives: {{{ [1 of 1] Compiling Main ( dist/setup/setup.hs, dist/setup/Main.o ) Linking ./dist/setup/setup ... Configuring distributive-0.5.2... real 0m21.580s user 0m20.928s sys 0m0.560s }}} while {{{ time cabal configure --ghc-options=-dynamic }}} gives: {{{ Resolving dependencies... [1 of 1] Compiling Main ( dist/setup/setup.hs, dist/setup/Main.o ) Linking ./dist/setup/setup ... Configuring distributive-0.5.2... real 0m1.830s user 0m1.460s sys 0m0.228s }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 26 08:46:15 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 26 Jun 2017 08:46:15 -0000 Subject: [GHC] #13875: ApplicativeDo desugaring is lazier than standard desugaring In-Reply-To: <045.2eda858359df0999208d04da5f95a1da@haskell.org> References: <045.2eda858359df0999208d04da5f95a1da@haskell.org> Message-ID: <060.2e2b71fa79ff3c1a5fa85aff7607885c@haskell.org> #13875: ApplicativeDo desugaring is lazier than standard desugaring -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: (none) Type: bug | Status: new Priority: high | Milestone: 8.2.1 Component: Compiler | Version: 8.3 Resolution: | Keywords: ApplicativeDo Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Other | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonmar): Wow, you're right. I hadn't realised this, and I think you're the first person to point it out. It's not limited to `Functor`, the problem occurs with `Applicative` too: {{{ Prelude Data.Maybe> :set -XApplicativeDo Prelude Data.Maybe> let f m = do () <- m; () <- m; return () Prelude Data.Maybe> :t f f :: Applicative f => f () -> f () Prelude Data.Maybe> isJust (f (Just undefined)) True }}} To fix this properly we would have to prevent `ApplicativeDo` from applying to any statement with a strict pattern match. In practice I doubt anyone is going to write `~p` to make `ApplicativeDo` work, but fortunately it still works for simple variable patterns. Ugh, I don't know what the best fix is here, but I agree at the very least we need some documentation. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 26 08:56:13 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 26 Jun 2017 08:56:13 -0000 Subject: [GHC] #13875: ApplicativeDo desugaring is lazier than standard desugaring In-Reply-To: <045.2eda858359df0999208d04da5f95a1da@haskell.org> References: <045.2eda858359df0999208d04da5f95a1da@haskell.org> Message-ID: <060.06f1c882f4022f854baa1a758463133f@haskell.org> #13875: ApplicativeDo desugaring is lazier than standard desugaring -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: simonmar Type: bug | Status: new Priority: high | Milestone: 8.2.1 Component: Compiler | Version: 8.3 Resolution: | Keywords: ApplicativeDo Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Other | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * owner: (none) => simonmar Comment: It's a subtle issue, not described in the paper. So yes we need something in the user manual, but a longer Note somewhere, linking to this ticket, giving example(s), and explaining our design choice, would be helpful. > To fix this properly we would have to prevent ApplicativeDo from applying to any statement with a strict pattern match. That would not be hard, would it? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 26 15:39:53 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 26 Jun 2017 15:39:53 -0000 Subject: =?utf-8?b?UmU6IFtHSENdICMxMzYxNTogTm9uZGV0ZXJtaW5pc20gaW4g4oCY?= =?utf-8?q?pure=E2=80=99_function_w/_parallel_evaluation_=26_memo?= =?utf-8?q?_combinators?= In-Reply-To: <044.57733831351687fff6258688df1f42f7@haskell.org> References: <044.57733831351687fff6258688df1f42f7@haskell.org> Message-ID: <059.28d8e39352169c21e6352e4e112bc1f5@haskell.org> #13615: Nondeterminism in ‘pure’ function w/ parallel evaluation & memo combinators -------------------------------------+------------------------------------- Reporter: pacak | Owner: bgamari Type: bug | Status: new Priority: highest | Milestone: 8.2.1 Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): Indeed disabling the duplicate-work-suspension logic in `threadPaused` prevents the issue from manifesting. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 26 15:40:35 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 26 Jun 2017 15:40:35 -0000 Subject: [GHC] #13875: ApplicativeDo desugaring is lazier than standard desugaring In-Reply-To: <045.2eda858359df0999208d04da5f95a1da@haskell.org> References: <045.2eda858359df0999208d04da5f95a1da@haskell.org> Message-ID: <060.712f9f5677e40a84620ee2dc31ea1763@haskell.org> #13875: ApplicativeDo desugaring is lazier than standard desugaring -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: simonmar Type: bug | Status: new Priority: high | Milestone: 8.2.1 Component: Compiler | Version: 8.3 Resolution: | Keywords: ApplicativeDo Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Other | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by dfeuer): Replying to [comment:3 simonmar]: > To fix this properly we would have to prevent `ApplicativeDo` from applying to any statement with a strict pattern match. In practice I doubt anyone is going to write `~p` to make `ApplicativeDo` work, but fortunately it still works for simple variable patterns. It seems terribly unfortunate, in my opinion, if adding a language extension to a module can, ''all by itself'', introduce a memory leak. The fix does seem annoying, but I don't think there's another good way. The current behavior is both surprising and inconsistent. We generally expect, for example, that {{{#!hs (x,y) <- m e }}} will be exactly the same as {{{#!hs xy <- m case xy of (x,y) -> e }}} but that's not currently the case. Here's an (arguably) more extreme example: {{{#!hs oops m = do !xy <- m pure (fst xy + snd xy) }}} With `ApplicativeDo`, the bang pattern is silently ignored. So I think the special desugaring should only be used if all the patterns are lazy. It might make sense to check whether an expression could ''otherwise'' be desugared specially, and offer an optional warning in that case. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 26 16:13:02 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 26 Jun 2017 16:13:02 -0000 Subject: [GHC] #13876: Check 'pure' method of 'Applicative (WrappedMonad m)' Message-ID: <051.5c5537466ef9d8fe586780eff30179d7@haskell.org> #13876: Check 'pure' method of 'Applicative (WrappedMonad m)' -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- Should {{{#!hs instance Monad m => Applicative (WrappedMonad m) where pure = WrapMonad . pure WrapMonad f <*> WrapMonad v = WrapMonad (f `ap` v) }}} not use `return`? {{{#!hs instance Monad m => Applicative (WrappedMonad m) where pure = WrapMonad . return WrapMonad f <*> WrapMonad v = WrapMonad (f `ap` v) }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 26 17:25:31 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 26 Jun 2017 17:25:31 -0000 Subject: [GHC] #13541: Make it easier to use the gold linker In-Reply-To: <046.0b1321a637ed3292c60514e6510d2c09@haskell.org> References: <046.0b1321a637ed3292c60514e6510d2c09@haskell.org> Message-ID: <061.1744876f388b7b7f556b8685b79f48de@haskell.org> #13541: Make it easier to use the gold linker -------------------------------------+------------------------------------- Reporter: bgamari | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #13810, #13739 | Differential Rev(s): Phab:D3449 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * related: #13810 => #13810, #13739 Comment: Simon Marlow has said that he would really like to see this happen in 8.2.1 due to the regressions in #13739. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 26 17:46:43 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 26 Jun 2017 17:46:43 -0000 Subject: [GHC] #13541: Make it easier to use the gold linker In-Reply-To: <046.0b1321a637ed3292c60514e6510d2c09@haskell.org> References: <046.0b1321a637ed3292c60514e6510d2c09@haskell.org> Message-ID: <061.4ea93156780150f8e5faba0d4f422ba3@haskell.org> #13541: Make it easier to use the gold linker -------------------------------------+------------------------------------- Reporter: bgamari | Owner: (none) Type: feature request | Status: new Priority: highest | Milestone: 8.2.1 Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #13810, #13739 | Differential Rev(s): Phab:D3449 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * priority: normal => highest * milestone: => 8.2.1 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 26 17:46:51 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 26 Jun 2017 17:46:51 -0000 Subject: [GHC] #13541: Make it easier to use the gold linker In-Reply-To: <046.0b1321a637ed3292c60514e6510d2c09@haskell.org> References: <046.0b1321a637ed3292c60514e6510d2c09@haskell.org> Message-ID: <061.ae1a34198822b9e22e26ee7d99d2b515@haskell.org> #13541: Make it easier to use the gold linker -------------------------------------+------------------------------------- Reporter: bgamari | Owner: bgamari Type: feature request | Status: new Priority: highest | Milestone: 8.2.1 Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #13810, #13739 | Differential Rev(s): Phab:D3449 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * owner: (none) => bgamari -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 26 18:05:51 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 26 Jun 2017 18:05:51 -0000 Subject: [GHC] #13877: GHC panic: No skolem info: k2 Message-ID: <050.85aac3d842c3e1851a442a13f59ce985@haskell.org> #13877: GHC panic: No skolem info: k2 -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 (Type checker) | Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: Compile-time Unknown/Multiple | crash or panic Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- The following code causes a GHC panic on GHC 8.0.1, 8.0.2, 8.2.1, and HEAD: {{{#!hs {-# LANGUAGE AllowAmbiguousTypes #-} {-# LANGUAGE ConstraintKinds #-} {-# LANGUAGE GADTs #-} {-# LANGUAGE RankNTypes #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE Trustworthy #-} {-# LANGUAGE TypeApplications #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE TypeInType #-} {-# LANGUAGE TypeOperators #-} module Eliminator where import Data.Kind data family Sing (a :: k) data instance Sing (z :: [a]) where SNil :: Sing '[] SCons :: Sing x -> Sing xs -> Sing (x:xs) data TyFun :: * -> * -> * type a ~> b = TyFun a b -> * infixr 0 ~> type family Apply (f :: k1 ~> k2) (x :: k1) :: k2 type a @@ b = Apply a b infixl 9 @@ data FunArrow = (:->) | (:~>) class FunType (arr :: FunArrow) where type Fun (k1 :: Type) arr (k2 :: Type) :: Type class FunType arr => AppType (arr :: FunArrow) where type App k1 arr k2 (f :: Fun k1 arr k2) (x :: k1) :: k2 type FunApp arr = (FunType arr, AppType arr) instance FunType (:->) where type Fun k1 (:->) k2 = k1 -> k2 $(return []) -- This is only necessary for GHC 8.0 -- GHC 8.2 is smarter instance AppType (:->) where type App k1 (:->) k2 (f :: k1 -> k2) x = f x instance FunType (:~>) where type Fun k1 (:~>) k2 = k1 ~> k2 $(return []) instance AppType (:~>) where type App k1 (:~>) k2 (f :: k1 ~> k2) x = f @@ x infixr 0 -?> type (-?>) (k1 :: Type) (k2 :: Type) (arr :: FunArrow) = Fun k1 arr k2 listElim :: forall (a :: Type) (p :: [a] -> Type) (l :: [a]). Sing l -> p '[] -> (forall (x :: a) (xs :: [a]). Sing x -> Sing xs -> p xs -> p (x:xs)) -> p l listElim = listElimPoly @(:->) @a @p @l listElimTyFun :: forall (a :: Type) (p :: [a] ~> Type) (l :: [a]). Sing l -> p @@ '[] -> (forall (x :: a) (xs :: [a]). Sing x -> Sing xs -> p @@ xs -> p @@ (x:xs)) -> p @@ l -- The line below causes a GHC panic. It should not typecheck; -- uncomment the line below it for the correct version listElimTyFun = listElimPoly @(:->) @a @p @l -- listElimTyFun = listElimPoly @(:~>) @a @p @l listElimPoly :: forall (arr :: FunArrow) (a :: Type) (p :: ([a] -?> Type) arr) (l :: [a]). FunApp arr => Sing l -> App [a] arr Type p '[] -> (forall (x :: a) (xs :: [a]). Sing x -> Sing xs -> App [a] arr Type p xs -> App [a] arr Type p (x:xs)) -> App [a] arr Type p l listElimPoly SNil pNil _ = pNil listElimPoly (SCons x (xs :: Sing xs)) pNil pCons = pCons x xs (listElimPoly @arr @a @p @xs xs pNil pCons) }}} {{{ $ /opt/ghc/8.2.1/bin/ghci Eliminator.hs GHCi, version 8.2.0.20170623: http://www.haskell.org/ghc/ :? for help Loaded GHCi configuration from /home/rgscott/.ghci [1 of 1] Compiling Eliminator ( Eliminator.hs, interpreted ) Eliminator.hs:72:17: error:ghc: panic! (the 'impossible' happened) (GHC version 8.2.0.20170623 for x86_64-unknown-linux): No skolem info: k2_a5cr Call stack: CallStack (from HasCallStack): prettyCurrentCallStack, called at compiler/utils/Outputable.hs:1133:58 in ghc:Outputable callStackDoc, called at compiler/utils/Outputable.hs:1137:37 in ghc:Outputable pprPanic, called at compiler/typecheck/TcErrors.hs:2653:5 in ghc:TcErrors Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 26 18:45:27 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 26 Jun 2017 18:45:27 -0000 Subject: [GHC] #13739: very slow linking of executables with ld.bfd < 2.27 In-Reply-To: <043.2d2650cd128632597774b5afb6c7a225@haskell.org> References: <043.2d2650cd128632597774b5afb6c7a225@haskell.org> Message-ID: <058.81ba61f3d99107fb5c0bedb91923bbcd@haskell.org> #13739: very slow linking of executables with ld.bfd < 2.27 -------------------------------------+------------------------------------- Reporter: duog | Owner: (none) Type: bug | Status: new Priority: high | Milestone: 8.2.1 Component: Compiler | Version: 8.2.1-rc2 Resolution: | Keywords: Operating System: Linux | Architecture: x86_64 Type of failure: Compile-time | (amd64) performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by nh2): * cc: nh2 (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 26 19:17:16 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 26 Jun 2017 19:17:16 -0000 Subject: [GHC] #13878: Implement SIMD support in NCG Message-ID: <046.76b0084aca4530db68df1d7ca477ae7f@haskell.org> #13878: Implement SIMD support in NCG -------------------------------------+------------------------------------- Reporter: bgamari | Owner: (none) Type: feature | Status: new request | Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 (NCG) | Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: wiki:SIMD -------------------------------------+------------------------------------- Currently [[SIMD]] is only supported in the LLVM code generator. This is a shame and makes functionality significantly harder to depend upon. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 26 19:17:42 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 26 Jun 2017 19:17:42 -0000 Subject: [GHC] #10286: native code generator: GHC crash at GHC.Prim SIMD vector In-Reply-To: <045.2537c47c79c85a06c9641d3e66088575@haskell.org> References: <045.2537c47c79c85a06c9641d3e66088575@haskell.org> Message-ID: <060.3791bc6e2b8e93b990170ab6392acfaa@haskell.org> #10286: native code generator: GHC crash at GHC.Prim SIMD vector -------------------------------------+------------------------------------- Reporter: hkanai | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: invalid | Keywords: Operating System: Linux | Architecture: x86_64 Type of failure: Compile-time | (amd64) crash | Test Case: Blocked By: | Blocking: Related Tickets: #13878 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * related: => #13878 Comment: I've opened #13878 to track the lack of SIMD support in the NCG. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 26 19:18:03 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 26 Jun 2017 19:18:03 -0000 Subject: [GHC] #10286: native code generator: GHC crash at GHC.Prim SIMD vector In-Reply-To: <045.2537c47c79c85a06c9641d3e66088575@haskell.org> References: <045.2537c47c79c85a06c9641d3e66088575@haskell.org> Message-ID: <060.341a8e5ae8fd66603dbc192d6c525215@haskell.org> #10286: native code generator: GHC crash at GHC.Prim SIMD vector -------------------------------------+------------------------------------- Reporter: hkanai | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: invalid | Keywords: SIMD Operating System: Linux | Architecture: x86_64 Type of failure: Compile-time | (amd64) crash | Test Case: Blocked By: | Blocking: Related Tickets: #13878 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * keywords: => SIMD -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 26 19:18:51 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 26 Jun 2017 19:18:51 -0000 Subject: [GHC] #12412: SIMD things introduce a metric ton of known key things In-Reply-To: <046.cd884b3e798e0694f3f465a42e24806f@haskell.org> References: <046.cd884b3e798e0694f3f465a42e24806f@haskell.org> Message-ID: <061.34e52ccedff41896ae1f2364b90e2859@haskell.org> #12412: SIMD things introduce a metric ton of known key things -------------------------------------+------------------------------------- Reporter: bgamari | Owner: (none) Type: bug | Status: new Priority: low | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: SIMD Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * keywords: => SIMD -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 26 19:19:07 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 26 Jun 2017 19:19:07 -0000 Subject: [GHC] #13852: Can we have more SIMD primops, corresponding to the untapped AVX etc. instructions? In-Reply-To: <054.7970fd47b788896732a324aafb5794c0@haskell.org> References: <054.7970fd47b788896732a324aafb5794c0@haskell.org> Message-ID: <069.cd34a67f76f02cfe5b8d3cfd77670b58@haskell.org> #13852: Can we have more SIMD primops, corresponding to the untapped AVX etc. instructions? -------------------------------------+------------------------------------- Reporter: leftaroundabout | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler (LLVM) | Version: 8.0.1 Resolution: | Keywords: SIMD Operating System: Unknown/Multiple | Architecture: x86_64 | (amd64) Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * keywords: => SIMD -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 26 19:19:40 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 26 Jun 2017 19:19:40 -0000 Subject: [GHC] #10648: Some 64-vector SIMD primitives are absolutely useless In-Reply-To: <044.c060f468a7f7b3021db9c517bef50f1b@haskell.org> References: <044.c060f468a7f7b3021db9c517bef50f1b@haskell.org> Message-ID: <059.ddac732a918e313f848208f26f4d43b2@haskell.org> #10648: Some 64-vector SIMD primitives are absolutely useless -------------------------------------+------------------------------------- Reporter: mniip | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: Resolution: | Keywords: SIMD Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * keywords: => SIMD -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 26 19:20:28 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 26 Jun 2017 19:20:28 -0000 Subject: [GHC] #13878: Implement SIMD support in NCG In-Reply-To: <046.76b0084aca4530db68df1d7ca477ae7f@haskell.org> References: <046.76b0084aca4530db68df1d7ca477ae7f@haskell.org> Message-ID: <061.66e221a790cb3beebde80f28073691cd@haskell.org> #13878: Implement SIMD support in NCG -------------------------------------+------------------------------------- Reporter: bgamari | Owner: (none) Type: feature request | Status: closed Priority: normal | Milestone: Component: Compiler (NCG) | Version: 8.0.1 Resolution: duplicate | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #7741 | Differential Rev(s): Wiki Page: wiki:SIMD | -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => closed * resolution: => duplicate * related: => #7741 Comment: Whoops, this is a duplicate of #7741. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 26 19:20:55 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 26 Jun 2017 19:20:55 -0000 Subject: [GHC] #7741: Add SIMD support to x86/x86_64 NCG In-Reply-To: <047.ec0118457b1e4a3b6ea3c008b0b9e4f2@haskell.org> References: <047.ec0118457b1e4a3b6ea3c008b0b9e4f2@haskell.org> Message-ID: <062.ef02a18ba1fd48f55c12ac0ba0d5bc95@haskell.org> #7741: Add SIMD support to x86/x86_64 NCG -------------------------------------+------------------------------------- Reporter: shelarcy | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler (NCG) | Version: 7.7 Resolution: | Keywords: SIMD Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: #3557 | Differential Rev(s): Wiki Page: wiki:SIMD | -------------------------------------+------------------------------------- Changes (by bgamari): * keywords: => SIMD * wikipage: => wiki:SIMD -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 26 19:21:49 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 26 Jun 2017 19:21:49 -0000 Subject: [GHC] #3557: CPU Vector instructions in GHC.Prim In-Reply-To: <044.db8b087837e05fdd9a6c4304c2acd80c@haskell.org> References: <044.db8b087837e05fdd9a6c4304c2acd80c@haskell.org> Message-ID: <059.281eb314ca297c6fc1f08e8f0f2fbcf0@haskell.org> #3557: CPU Vector instructions in GHC.Prim -------------------------------------+------------------------------------- Reporter: guest | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: ⊥ Component: Data Parallel | Version: 6.11 Haskell | Resolution: | Keywords: SIMD Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * keywords: => SIMD -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 26 19:22:24 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 26 Jun 2017 19:22:24 -0000 Subject: [GHC] #8033: add AVX register support to llvm calling convention In-Reply-To: <045.7dc8866bbad0b343f7d0cca58aa9a9b3@haskell.org> References: <045.7dc8866bbad0b343f7d0cca58aa9a9b3@haskell.org> Message-ID: <060.c6593820634e3d0e01ce28459569b3a2@haskell.org> #8033: add AVX register support to llvm calling convention -------------------------------------+------------------------------------- Reporter: carter | Owner: carter Type: task | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 7.7 Resolution: invalid | Keywords: SIMD Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * keywords: => SIMD -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 26 19:29:36 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 26 Jun 2017 19:29:36 -0000 Subject: [GHC] #13739: very slow linking of executables with ld.bfd < 2.27 In-Reply-To: <043.2d2650cd128632597774b5afb6c7a225@haskell.org> References: <043.2d2650cd128632597774b5afb6c7a225@haskell.org> Message-ID: <058.d5b78f1d3ac39c43a963196a45f27d40@haskell.org> #13739: very slow linking of executables with ld.bfd < 2.27 -------------------------------------+------------------------------------- Reporter: duog | Owner: (none) Type: bug | Status: new Priority: high | Milestone: 8.2.1 Component: Compiler | Version: 8.2.1-rc2 Resolution: | Keywords: Operating System: Linux | Architecture: x86_64 Type of failure: Compile-time | (amd64) performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by nh2): I have filed an upstream GNU ld bug to ask whether they are aware what could have brought the 10x performance improvement that ld 2.27 brought over 2.26: https://sourceware.org/bugzilla/show_bug.cgi?id=21677 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 26 19:34:40 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 26 Jun 2017 19:34:40 -0000 Subject: [GHC] #8033: add AVX register support to llvm calling convention In-Reply-To: <045.7dc8866bbad0b343f7d0cca58aa9a9b3@haskell.org> References: <045.7dc8866bbad0b343f7d0cca58aa9a9b3@haskell.org> Message-ID: <060.df4ac603af8d3016d1087cdbe45af8ac@haskell.org> #8033: add AVX register support to llvm calling convention -------------------------------------+------------------------------------- Reporter: carter | Owner: (none) Type: task | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.7 Resolution: | Keywords: SIMD Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * owner: carter => (none) * status: closed => new * resolution: invalid => Comment: Reopening as this still hasn't been done. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 26 19:39:31 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 26 Jun 2017 19:39:31 -0000 Subject: [GHC] #13876: Check 'pure' method of 'Applicative (WrappedMonad m)' In-Reply-To: <051.5c5537466ef9d8fe586780eff30179d7@haskell.org> References: <051.5c5537466ef9d8fe586780eff30179d7@haskell.org> Message-ID: <066.acd82edd7e348908b7005b1ff4c9fd42@haskell.org> #13876: Check 'pure' method of 'Applicative (WrappedMonad m)' -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * cc: hvr, ekmett, core-libraries-committee@… (added) Comment: Perhaps. However, given that `pure` and `return` shouldn't differ, and that the "`Monad` of no `return`" was seriously considered, it's not clear to me whether it matters enough to change it. The moment `pure /= return` you have bigger problems. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 26 19:43:20 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 26 Jun 2017 19:43:20 -0000 Subject: [GHC] #13876: Check 'pure' method of 'Applicative (WrappedMonad m)' In-Reply-To: <051.5c5537466ef9d8fe586780eff30179d7@haskell.org> References: <051.5c5537466ef9d8fe586780eff30179d7@haskell.org> Message-ID: <066.913e634988d63dc911a0d8d8ad755186@haskell.org> #13876: Check 'pure' method of 'Applicative (WrappedMonad m)' -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): Indeed, this was changed from `pure = WrapMonad. return` to `pure = WrapMonad . pure` in e737a5126dcfdd0610587d2ec16bea6481cf2a42 (`base: MRP- refactoring of AMP instances`), so perhaps hvr should chime in here. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 26 20:55:27 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 26 Jun 2017 20:55:27 -0000 Subject: [GHC] #13879: Strange interaction between higher-rank kinds and type synonyms Message-ID: <050.03cb88421049abbd653e9048089d3969@haskell.org> #13879: Strange interaction between higher-rank kinds and type synonyms -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 (Type checker) | Keywords: TypeInType | Operating System: Unknown/Multiple Architecture: | Type of failure: GHC rejects Unknown/Multiple | valid program Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- Here's some code with typechecks with GHC 8.0.1, 8.0.2, 8.2.1, and HEAD: {{{#!hs {-# LANGUAGE GADTs #-} {-# LANGUAGE RankNTypes #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE TypeInType #-} {-# LANGUAGE TypeOperators #-} module Bug where import Data.Kind data family Sing (a :: k) data (a :: j) :~~: (b :: k) where HRefl :: a :~~: a data instance Sing (z :: a :~~: b) where SHRefl :: Sing HRefl (%:~~:->) :: forall (j :: Type) (k :: Type) (a :: j) (b :: k) (r :: a :~~: b) (p :: forall (z :: Type) (y :: z). a :~~: y -> Type). Sing r -> p HRefl -> p r (%:~~:->) SHRefl pHRefl = pHRefl type App f x = f x type HRApp (f :: forall (z :: Type) (y :: z). a :~~: y -> Type) (x :: a :~~: b) = f x }}} Now I want to refactor this so that I use `App`: {{{#!hs (%:~~:->) :: forall (j :: Type) (k :: Type) (a :: j) (b :: k) (r :: a :~~: b) (p :: forall (z :: Type) (y :: z). a :~~: y -> Type). Sing r -> App p HRefl -> App p r }}} However, GHC doesn't like that: {{{ $ /opt/ghc/8.2.1/bin/ghci Bug.hs -fprint-explicit-kinds -fprint-explicit- foralls GHCi, version 8.2.0.20170623: http://www.haskell.org/ghc/ :? for help Loaded GHCi configuration from /home/rgscott/.ghci [1 of 1] Compiling Bug ( Bug.hs, interpreted ) Bug.hs:21:20: error: • Expected kind ‘(:~~:) j z a a’, but ‘'HRefl j a’ has kind ‘(:~~:) j j a a’ • In the second argument of ‘App’, namely ‘HRefl’ In the type signature: (%:~~:->) :: forall (j :: Type) (k :: Type) (a :: j) (b :: k) (r :: a :~~: b) (p :: forall (z :: Type) (y :: z). a :~~: y -> Type). Sing r -> App p HRefl -> App p r | 21 | -> App p HRefl | ^^^^^ Bug.hs:22:20: error: • Expected kind ‘(:~~:) j z a b’, but ‘r’ has kind ‘(:~~:) j k a b’ • In the second argument of ‘App’, namely ‘r’ In the type signature: (%:~~:->) :: forall (j :: Type) (k :: Type) (a :: j) (b :: k) (r :: a :~~: b) (p :: forall (z :: Type) (y :: z). a :~~: y -> Type). Sing r -> App p HRefl -> App p r | 22 | -> App p r | ^ }}} These errors are surprising to me, since it appears that the two higher- rank types, `z` and `y`, are behaving differently here: `y` appears to be willing to unify with other types in applications of `p`, but `z` isn't! I would expect //both// to be willing to unify in applications of `p`. Out of desperation, I tried this other formulation of `(%:~~:->)` which uses `HRApp` instead of `App`: {{{#!hs (%:~~:->) :: forall (j :: Type) (k :: Type) (a :: j) (b :: k) (r :: a :~~: b) (p :: forall (z :: Type) (y :: z). a :~~: y -> Type). Sing r -> HRApp p HRefl -> HRApp p r }}} But now I get an even stranger error message: {{{ $ /opt/ghc/8.2.1/bin/ghci Bug.hs -fprint-explicit-kinds -fprint-explicit- foralls GHCi, version 8.2.0.20170623: http://www.haskell.org/ghc/ :? for help Loaded GHCi configuration from /home/rgscott/.ghci [1 of 1] Compiling Bug ( Bug.hs, interpreted ) Bug.hs:21:20: error: • Expected kind ‘forall z (y :: z). (:~~:) j z a y -> *’, but ‘p’ has kind ‘forall z (y :: z). (:~~:) j z a y -> *’ • In the first argument of ‘HRApp’, namely ‘p’ In the type signature: (%:~~:->) :: forall (j :: Type) (k :: Type) (a :: j) (b :: k) (r :: a :~~: b) (p :: forall (z :: Type) (y :: z). a :~~: y -> Type). Sing r -> HRApp p HRefl -> HRApp p r | 21 | -> HRApp p HRefl | ^ Bug.hs:21:20: error: • Expected kind ‘forall z (y :: z). (:~~:) j z a y -> *’, but ‘p’ has kind ‘forall z (y :: z). (:~~:) j z a y -> *’ • In the first argument of ‘HRApp’, namely ‘p’ In the type signature: (%:~~:->) :: forall (j :: Type) (k :: Type) (a :: j) (b :: k) (r :: a :~~: b) (p :: forall (z :: Type) (y :: z). a :~~: y -> Type). Sing r -> HRApp p HRefl -> HRApp p r | 21 | -> HRApp p HRefl | ^ Bug.hs:22:20: error: • Expected kind ‘forall z (y :: z). (:~~:) j z a y -> *’, but ‘p’ has kind ‘forall z (y :: z). (:~~:) j z a y -> *’ • In the first argument of ‘HRApp’, namely ‘p’ In the type signature: (%:~~:->) :: forall (j :: Type) (k :: Type) (a :: j) (b :: k) (r :: a :~~: b) (p :: forall (z :: Type) (y :: z). a :~~: y -> Type). Sing r -> HRApp p HRefl -> HRApp p r | 22 | -> HRApp p r | ^ }}} That's right, it can't match the kinds: * `forall z (y :: z). (:~~:) j z a y -> *`, and * `forall z (y :: z). (:~~:) j z a y -> *` Uh... what? Those are the same kind! -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 26 21:26:03 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 26 Jun 2017 21:26:03 -0000 Subject: [GHC] #13866: -g doesn't work with -pgma=clang++ In-Reply-To: <046.0cc5ec25fa742bf402aa06da26adeede@haskell.org> References: <046.0cc5ec25fa742bf402aa06da26adeede@haskell.org> Message-ID: <061.44881a6d0409099c2cab059711f8c087@haskell.org> #13866: -g doesn't work with -pgma=clang++ ---------------------------------+---------------------------------------- Reporter: niteria | Owner: (none) Type: bug | Status: patch Priority: normal | Milestone: 8.2.1 Component: Compiler | Version: 8.3 Resolution: | Keywords: Operating System: Linux | Architecture: Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3667 Wiki Page: | ---------------------------------+---------------------------------------- Comment (by Ben Gamari ): In [changeset:"904255eb9b537103898fb5f6b73df9b53ca7fd93/ghc" 904255eb/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="904255eb9b537103898fb5f6b73df9b53ca7fd93" DWARF: Use .short to render half-machine-words The binutils documentation states that .short is a synonym for .word, which I assumed to mean "machine word", leading me to believe that we needed to use .hword to render half-machine-words. However, Darwin's toolchain doesn't understand .hword, so there we instead used .short. However, as it turns out the binutils documentation confusingly uses "word" to refer to a 16-bit word, so .short should work fine. Moreover, LLVM's internal assembler also doesn't understand .hword, so using .short consistently simplies things remarkably. Test Plan: Validate using binutils and LLVM internal assembler, validate on Darwin Reviewers: niteria, austin Reviewed By: niteria Subscribers: rwbarton, thomie GHC Trac Issues: #13866 Differential Revision: https://phabricator.haskell.org/D3667 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 26 21:26:03 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 26 Jun 2017 21:26:03 -0000 Subject: [GHC] #13864: RTS Stats are recorded without -T In-Reply-To: <044.9df229b07a94d2f8126cf8d8d9d18c67@haskell.org> References: <044.9df229b07a94d2f8126cf8d8d9d18c67@haskell.org> Message-ID: <059.d4196e174eeeeca613d89609c37a0618@haskell.org> #13864: RTS Stats are recorded without -T -------------------------------------+------------------------------------- Reporter: glguy | Owner: (none) Type: bug | Status: patch Priority: normal | Milestone: 8.2.1 Component: Runtime System | Version: 8.2.1-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3669 Wiki Page: | -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"4bd4f561d79de4d056571eca61a5249a5091c985/ghc" 4bd4f56/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="4bd4f561d79de4d056571eca61a5249a5091c985" rts: Always collect stats It seems that 12ad4d417b89462ba8e19a3c7772a931b3a93f0e enabled collection by default as its needs stats.allocated_bytes to determine whether the program has exceeded its grace limit. However, enabling stats also enables some potentially expensive times checks. In general GC statistics should be cheap to compute (relative to the GC itself), so now we always compute them. This allows us to once again disable giveStats by default. Fixes #13864. Reviewers: simonmar, austin, erikd Reviewed By: simonmar Subscribers: rwbarton, thomie GHC Trac Issues: #13864 Differential Revision: https://phabricator.haskell.org/D3669 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 26 21:46:27 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 26 Jun 2017 21:46:27 -0000 Subject: [GHC] #13866: -g doesn't work with -pgma=clang++ In-Reply-To: <046.0cc5ec25fa742bf402aa06da26adeede@haskell.org> References: <046.0cc5ec25fa742bf402aa06da26adeede@haskell.org> Message-ID: <061.e9dfe14607cede070b37f24a1c0cf061@haskell.org> #13866: -g doesn't work with -pgma=clang++ ---------------------------------+---------------------------------------- Reporter: niteria | Owner: (none) Type: bug | Status: merge Priority: normal | Milestone: 8.2.1 Component: Compiler | Version: 8.3 Resolution: | Keywords: Operating System: Linux | Architecture: Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3667 Wiki Page: | ---------------------------------+---------------------------------------- Changes (by bgamari): * status: patch => merge -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 26 21:46:55 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 26 Jun 2017 21:46:55 -0000 Subject: [GHC] #13864: RTS Stats are recorded without -T In-Reply-To: <044.9df229b07a94d2f8126cf8d8d9d18c67@haskell.org> References: <044.9df229b07a94d2f8126cf8d8d9d18c67@haskell.org> Message-ID: <059.0e39b179839916b10b057dfa97c9f17c@haskell.org> #13864: RTS Stats are recorded without -T -------------------------------------+------------------------------------- Reporter: glguy | Owner: (none) Type: bug | Status: merge Priority: normal | Milestone: 8.2.1 Component: Runtime System | Version: 8.2.1-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3669 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: patch => merge -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 26 22:29:23 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 26 Jun 2017 22:29:23 -0000 Subject: [GHC] #13864: RTS Stats are recorded without -T In-Reply-To: <044.9df229b07a94d2f8126cf8d8d9d18c67@haskell.org> References: <044.9df229b07a94d2f8126cf8d8d9d18c67@haskell.org> Message-ID: <059.890be18726b4096bae65015b690a440e@haskell.org> #13864: RTS Stats are recorded without -T -------------------------------------+------------------------------------- Reporter: glguy | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.2.1 Component: Runtime System | Version: 8.2.1-rc2 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3669 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: merge => closed * resolution: => fixed Comment: Merged in f19ab07b660589bc7cc04073b9c91fac4be384e1. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 26 22:29:52 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 26 Jun 2017 22:29:52 -0000 Subject: [GHC] #13866: -g doesn't work with -pgma=clang++ In-Reply-To: <046.0cc5ec25fa742bf402aa06da26adeede@haskell.org> References: <046.0cc5ec25fa742bf402aa06da26adeede@haskell.org> Message-ID: <061.e7752cf4af9ae438db3bc0df448ab344@haskell.org> #13866: -g doesn't work with -pgma=clang++ ---------------------------------+---------------------------------------- Reporter: niteria | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.2.1 Component: Compiler | Version: 8.3 Resolution: fixed | Keywords: Operating System: Linux | Architecture: Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3667 Wiki Page: | ---------------------------------+---------------------------------------- Changes (by bgamari): * status: merge => closed * resolution: => fixed Comment: Merged in bed2ff7f26319d7ee4c5be0ee66c48e13c08a1a5. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 26 22:32:37 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 26 Jun 2017 22:32:37 -0000 Subject: [GHC] #13879: Strange interaction between higher-rank kinds and type synonyms In-Reply-To: <050.03cb88421049abbd653e9048089d3969@haskell.org> References: <050.03cb88421049abbd653e9048089d3969@haskell.org> Message-ID: <065.bb5270b338bc9e9d573722b69da986d4@haskell.org> #13879: Strange interaction between higher-rank kinds and type synonyms -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.1 checker) | Resolution: | Keywords: TypeInType Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): I could not resist investigating. Here are my conclusions. * With a DEBUG compiler, I immediately tripped over {{{ ASSERT failed! in_scope InScope {z_aUa y_aUb} tenv [aSo :-> z0_aUa[tau:1], aSp :-> y0_aUb[tau:1]] cenv [] tys [(:~~:) j0_aU1[tau:1] k0_aU2[tau:1] a_aSl[sk:1] y_aSp[sk:1] -> *] cos [] needInScope [aSj :-> j_aSj[sk:1], aSl :-> a_aSl[sk:1], aU1 :-> j_aU1[tau:1], aU2 :-> k_aU2[tau:1]] Call stack: CallStack (from HasCallStack): prettyCurrentCallStack, called at compiler\utils\Outputable.hs:1133:58 in ghc:Outputable callStackDoc, called at compiler\utils\Outputable.hs:1188:22 in ghc:Outputable assertPprPanic, called at compiler\types\TyCoRep.hs:2099:51 in ghc:TyCoRep checkValidSubst, called at compiler\types\TyCoRep.hs:2122:29 in ghc:TyCoRep substTy, called at compiler\typecheck\TcHsType.hs:936:27 in ghc:TcHsType }}} This was just a missing in-scope set setup in `TcHsType.instantiateTyN`. Easy to fix. * Next up, the original program. The bug here was that in a type signature like {{{ f :: forall (p :: forall z (y::z). ). }}} when instanting p's kind at occurrences of p in it's crucial that the kind we instantiate is fully zonked, else we may fail to substitute properly. But `tcLHsKind` (which converts the `LHsKind` to a `Kind` didn't zonk its result. Also easily fixed, and that makes the original program work. * Next, the mysterious message when you use `HRApp`. This arises because we try to unify the kinds {{{ forall z1 (y1::z1). HR a1 b1 c1 d1 ~# forall z2 (y2::z2). HR a2 b2 c2 d2 }}} (I'm using `HR` instead of infix `:~~:`, just to keep my head straight.) The first thing is that, at least by the time the constraint solver gets it, if we zonked LHS and RHS we'd see they were equal. But that's a small thing. What we do in `TcCanonical` is this: {{{ can_eq_nc' _flat _rdr_env _envs ev eq_rel s1@(ForAllTy {}) _ s2@(ForAllTy {}) _ | CtWanted { ctev_loc = loc, ctev_dest = orig_dest } <- ev = do { let (bndrs1,body1) = tcSplitForAllTyVarBndrs s1 (bndrs2,body2) = tcSplitForAllTyVarBndrs s2 ; kind_cos <- zipWithM (unifyWanted loc Nominal) (map binderKind bndrs1) (map binderKind bndrs2) ; all_co <- deferTcSForAllEq (eqRelRole eq_rel) loc kind_cos (bndrs1,body1) (bndrs2,body2) ; setWantedEq orig_dest all_co ; stopWith ev "Deferred polytype equality" } }}} Look at that `zipWithM`. It's obvously bogus in the case above, because we produce a constraint `z1~z2` which is insoluble. I need Richard's help here; but I think we just need to spit out that kind equality ''inside'' the new implication constraint, and after the alpha-renaming, rather than outside and before. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 26 22:39:19 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 26 Jun 2017 22:39:19 -0000 Subject: [GHC] #13739: very slow linking of executables with ld.bfd < 2.27 In-Reply-To: <043.2d2650cd128632597774b5afb6c7a225@haskell.org> References: <043.2d2650cd128632597774b5afb6c7a225@haskell.org> Message-ID: <058.87299dfcb56ddca1b5146f5432d1fa0d@haskell.org> #13739: very slow linking of executables with ld.bfd < 2.27 -------------------------------------+------------------------------------- Reporter: duog | Owner: (none) Type: bug | Status: infoneeded Priority: high | Milestone: 8.2.1 Component: Compiler | Version: 8.2.1-rc2 Resolution: | Keywords: Operating System: Linux | Architecture: x86_64 Type of failure: Compile-time | (amd64) performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => infoneeded * cc: nh2 (removed) Comment: I don't think there's much else that we can do about this. binutils 2.27 seems to fix the majority of the issue and ultimately the plan is to use `gold` more often anyways (see #13541). -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 26 22:40:58 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 26 Jun 2017 22:40:58 -0000 Subject: [GHC] #13739: very slow linking of executables with ld.bfd < 2.27 In-Reply-To: <043.2d2650cd128632597774b5afb6c7a225@haskell.org> References: <043.2d2650cd128632597774b5afb6c7a225@haskell.org> Message-ID: <058.f7c3829e9c4b1bf0b06682d451215dba@haskell.org> #13739: very slow linking of executables with ld.bfd < 2.27 -------------------------------------+------------------------------------- Reporter: duog | Owner: (none) Type: bug | Status: infoneeded Priority: high | Milestone: 8.2.1 Component: Compiler | Version: 8.2.1-rc2 Resolution: | Keywords: Operating System: Linux | Architecture: x86_64 Type of failure: Compile-time | (amd64) performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * cc: nh2 (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 26 22:41:39 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 26 Jun 2017 22:41:39 -0000 Subject: [GHC] #13702: GHC can't produce position independent executables In-Reply-To: <046.3c2d010e4ff43df6076d32ac62165117@haskell.org> References: <046.3c2d010e4ff43df6076d32ac62165117@haskell.org> Message-ID: <061.9c75f9783ede9036d43c4795a45ceca3@haskell.org> #13702: GHC can't produce position independent executables -------------------------------------+------------------------------------- Reporter: bgamari | Owner: bgamari Type: bug | Status: patch Priority: high | Milestone: 8.2.1 Component: Compiler | Version: 8.0.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3589 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * owner: (none) => bgamari -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 26 22:42:28 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 26 Jun 2017 22:42:28 -0000 Subject: [GHC] #13426: compile-time memory-usage regression for DynFlags between GHC 8.0 and GHC 8.2 In-Reply-To: <042.588059ee1290b666bd7f0947c071e1ff@haskell.org> References: <042.588059ee1290b666bd7f0947c071e1ff@haskell.org> Message-ID: <057.c57a825d4cf0fd0b41649e42730426c8@haskell.org> #13426: compile-time memory-usage regression for DynFlags between GHC 8.0 and GHC 8.2 -------------------------------------+------------------------------------- Reporter: hvr | Owner: dfeuer Type: bug | Status: new Priority: high | Milestone: 8.2.2 Component: Compiler | Version: 8.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3399, Wiki Page: | Phab:D3400, Phab:D3421 -------------------------------------+------------------------------------- Changes (by bgamari): * owner: (none) => dfeuer * milestone: 8.2.1 => 8.2.2 Comment: dfeuer is going to look into eliminating the need for `coreBindsSize` on every simplifier pass. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 26 22:42:39 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 26 Jun 2017 22:42:39 -0000 Subject: [GHC] #13426: compile-time memory-usage regression for DynFlags between GHC 8.0 and GHC 8.2 In-Reply-To: <042.588059ee1290b666bd7f0947c071e1ff@haskell.org> References: <042.588059ee1290b666bd7f0947c071e1ff@haskell.org> Message-ID: <057.f479fd30741ee36df96df657c90638e6@haskell.org> #13426: compile-time memory-usage regression for DynFlags between GHC 8.0 and GHC 8.2 -------------------------------------+------------------------------------- Reporter: hvr | Owner: dfeuer Type: bug | Status: new Priority: high | Milestone: 8.4.1 Component: Compiler | Version: 8.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3399, Wiki Page: | Phab:D3400, Phab:D3421 -------------------------------------+------------------------------------- Changes (by bgamari): * milestone: 8.2.2 => 8.4.1 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 26 22:53:26 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 26 Jun 2017 22:53:26 -0000 Subject: [GHC] #8684: hWaitForInput cannot be interrupted by async exceptions on unix In-Reply-To: <042.bed34cc32ec4222496f7d8b921c80c8a@haskell.org> References: <042.bed34cc32ec4222496f7d8b921c80c8a@haskell.org> Message-ID: <057.1412618178f3f9b138327ea29d17838a@haskell.org> #8684: hWaitForInput cannot be interrupted by async exceptions on unix -------------------------------------+------------------------------------- Reporter: nh2 | Owner: snoyberg Type: bug | Status: patch Priority: normal | Milestone: Component: Core Libraries | Version: 7.6.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D42 Wiki Page: | -------------------------------------+------------------------------------- Comment (by nh2): Replying to [comment:8 nh2]: > On ghc 8.0.2, this crashes with `fdReady: msecs != 0, this shouldn't happen`. This is fixed for GHC 8.2 per #13525 (https://phabricator.haskell.org/rGHCe5732d2a28dfb8a754ee73e124e3558222a543bb) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 26 23:00:58 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 26 Jun 2017 23:00:58 -0000 Subject: [GHC] #8281: The impossible happened: primRepToFFIType In-Reply-To: <044.47e20917996e473150de04c1ce1afc0b@haskell.org> References: <044.47e20917996e473150de04c1ce1afc0b@haskell.org> Message-ID: <059.27792f05b69f1542b69d88f8613dea28@haskell.org> #8281: The impossible happened: primRepToFFIType -------------------------------------+------------------------------------- Reporter: tibbe | Owner: (none) Type: bug | Status: patch Priority: high | Milestone: 8.4.1 Component: Compiler | Version: 7.6.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3619 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => patch * differential: => Phab:D3619 Comment: There is a currently-untested patch for this in Phab:D3619. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 26 23:13:51 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 26 Jun 2017 23:13:51 -0000 Subject: [GHC] #13875: ApplicativeDo desugaring is lazier than standard desugaring In-Reply-To: <045.2eda858359df0999208d04da5f95a1da@haskell.org> References: <045.2eda858359df0999208d04da5f95a1da@haskell.org> Message-ID: <060.ed6a32e752cfbe6c446ab8d86ed20d17@haskell.org> #13875: ApplicativeDo desugaring is lazier than standard desugaring -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: simonmar Type: bug | Status: new Priority: high | Milestone: 8.2.1 Component: Compiler | Version: 8.3 Resolution: | Keywords: ApplicativeDo Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Other | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by dfeuer): Yet another few thoughts. This is a situation that could be improved offering, in addition, separate `ado` syntax. Such syntax would offer deeply-lazy-always pattern matching, prohibit inappropriate bangs, and throw an error if desugaring would require `>>=`. Along with setting laziness appropriately, this would allow the user to declare that they expect applicative optimizations to kick in, even when a monad is actually available. While I'm mentioning idle thoughts: monad comprehension syntax seems to handle the `pure`/`return`/`pure $`/whatever issue a lot more cleanly than anything `do`-like. Has anyone considered applicative comprehensions? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 26 23:14:24 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 26 Jun 2017 23:14:24 -0000 Subject: [GHC] #13739: very slow linking of executables with ld.bfd < 2.27 In-Reply-To: <043.2d2650cd128632597774b5afb6c7a225@haskell.org> References: <043.2d2650cd128632597774b5afb6c7a225@haskell.org> Message-ID: <058.379b912f4e12f40b2a85bbcfbc4dd11b@haskell.org> #13739: very slow linking of executables with ld.bfd < 2.27 -------------------------------------+------------------------------------- Reporter: duog | Owner: (none) Type: bug | Status: infoneeded Priority: high | Milestone: 8.2.1 Component: Compiler | Version: 8.2.1-rc2 Resolution: | Keywords: Operating System: Linux | Architecture: x86_64 Type of failure: Compile-time | (amd64) performance bug | Test Case: Blocked By: | Blocking: Related Tickets: 13541 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by duog): * related: => 13541 Comment: I don't know whether anyone has investigated whether there is anything we are doing which is exasperating the problem. Executables produced by removing -Wl,--gc-sections from the linker invocation look like they're pulling in most of the archives. This does not occur with 8.0.2. I will see if it happens with gold once support it lands in the ghc-8.2 branch. I would like to see the configure scripts disable split sectioned libraries if the linker is ld.bfd < 27, or at least warn that the user is in for an unpleasant experience. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 26 23:18:17 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 26 Jun 2017 23:18:17 -0000 Subject: [GHC] #13876: Check 'pure' method of 'Applicative (WrappedMonad m)' In-Reply-To: <051.5c5537466ef9d8fe586780eff30179d7@haskell.org> References: <051.5c5537466ef9d8fe586780eff30179d7@haskell.org> Message-ID: <066.4d51a507c050c5f5b4bc6e6359e9b4fb@haskell.org> #13876: Check 'pure' method of 'Applicative (WrappedMonad m)' -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Iceland_jack): Replying to [comment:1 bgamari]: > Perhaps. However, given that `pure` and `return` shouldn't differ, and that the "`Monad` of no `return`" was seriously considered, it's not clear to me whether it matters enough to change it. The moment `pure /= return` you have bigger problems. It matters in the following code: {{{#!hs {-# Language TypeApplications, ScopedTypeVariables, InstanceSigs, RankNTypes, DeriveFunctor, GeneralizedNewtypeDeriving #-} import Control.Monad import Data.Coerce -- As in Control.Applicative newtype WrappedMonad m a = WrapMonad { unwrapMonad :: m a } deriving (Monad) instance Monad m => Functor (WrappedMonad m) where fmap :: (a -> b) -> (WrappedMonad m a -> WrappedMonad m b) fmap f (WrapMonad v) = WrapMonad (liftM f v) instance Monad m => Applicative (WrappedMonad m) where pure :: a -> WrappedMonad m a pure = WrapMonad . pure (<*>) :: WrappedMonad m (a -> b) -> WrappedMonad m a -> WrappedMonad m b WrapMonad f <*> WrapMonad v = WrapMonad (f `ap` v) -- Definition defining `Applicative' roundtripping through `WrappedMonad' data V3 a = V3 a a a deriving (Functor, Show) instance Applicative V3 where pure :: forall a. a -> V3 a pure = coerce (pure @(WrappedMonad V3) @a) (<*>) :: forall a b. V3 (a -> b) -> V3 a -> V3 b (<*>) = coerce ((<*>) @(WrappedMonad V3) @a @b) instance Monad V3 where return :: a -> V3 a return a = V3 a a a (>>=) :: V3 a -> (a -> V3 b) -> V3 b V3 a b c >>= f = V3 a' b' c' where V3 a' _ _ = f a V3 _ b' _ = f b V3 _ _ c' = f c }}} If we try to run `pure @V3 'a'` it loops.. but replace `pure = WrapMonad . pure` by `pure = WrapMonad . return` and it works as expected. but comment `Control.Applicative` out and un-comment the definition of `WrapMonad` (th -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 26 23:20:06 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 26 Jun 2017 23:20:06 -0000 Subject: [GHC] #13739: very slow linking of executables with ld.bfd < 2.27 In-Reply-To: <043.2d2650cd128632597774b5afb6c7a225@haskell.org> References: <043.2d2650cd128632597774b5afb6c7a225@haskell.org> Message-ID: <058.88742a3b8ef11eb73e424ee8a37ff432@haskell.org> #13739: very slow linking of executables with ld.bfd < 2.27 -------------------------------------+------------------------------------- Reporter: duog | Owner: (none) Type: bug | Status: infoneeded Priority: high | Milestone: 8.2.1 Component: Compiler | Version: 8.2.1-rc2 Resolution: | Keywords: Operating System: Linux | Architecture: x86_64 Type of failure: Compile-time | (amd64) performance bug | Test Case: Blocked By: | Blocking: Related Tickets: 13541 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by duog): Also, would anyone be able to check whether this occurs for non ELF targets? The thread linked to in comment 25 suggests some candidates for the fix in 2.27, both of which are ELF specific. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 26 23:36:16 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 26 Jun 2017 23:36:16 -0000 Subject: [GHC] #8684: hWaitForInput cannot be interrupted by async exceptions on unix In-Reply-To: <042.bed34cc32ec4222496f7d8b921c80c8a@haskell.org> References: <042.bed34cc32ec4222496f7d8b921c80c8a@haskell.org> Message-ID: <057.680eea4f14055db7a361101df30d165f@haskell.org> #8684: hWaitForInput cannot be interrupted by async exceptions on unix -------------------------------------+------------------------------------- Reporter: nh2 | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Core Libraries | Version: 7.6.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D42 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: patch => new * owner: snoyberg => (none) Comment: Sorry, it looks like I was mistaken; this is in fact not fixed. The `timeout` does not, in fact, interrupt the `hWaitForInput`. It looks like Phab:D42 was never actually finished. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jun 27 03:48:49 2017 From: ghc-devs at haskell.org (GHC) Date: Tue, 27 Jun 2017 03:48:49 -0000 Subject: [GHC] #13701: GHCi 2x slower without -keep-tmp-files In-Reply-To: <046.5313c8330fb56c9723008f1f4396a25a@haskell.org> References: <046.5313c8330fb56c9723008f1f4396a25a@haskell.org> Message-ID: <061.62db16826d2453b4cd1db88fe42cbc8d@haskell.org> #13701: GHCi 2x slower without -keep-tmp-files -------------------------------------+------------------------------------- Reporter: niteria | Owner: duog Type: task | Status: closed Priority: normal | Milestone: 8.4.1 Component: GHCi | Version: 8.3 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: T13701 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3620 Wiki Page: | -------------------------------------+------------------------------------- Comment (by nomeata): At least on perf.haskell.org, this test case is very flaky, and varies a lot between runs. So if you come here confused because your unrelated change looks like a regression, then that might just be the reason. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jun 27 04:22:06 2017 From: ghc-devs at haskell.org (GHC) Date: Tue, 27 Jun 2017 04:22:06 -0000 Subject: [GHC] #13863: -fno-code is broken on package:language-c-quote In-Reply-To: <043.24c6df62c4ee22a450d0662d44837518@haskell.org> References: <043.24c6df62c4ee22a450d0662d44837518@haskell.org> Message-ID: <058.1ff3ac64bc95c5de0f05b08b9e4dd714@haskell.org> #13863: -fno-code is broken on package:language-c-quote -------------------------------------+------------------------------------- Reporter: duog | Owner: duog Type: bug | Status: patch Priority: normal | Milestone: Component: Compiler | Version: 8.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | quasiquotation/T13863 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3677 Wiki Page: | -------------------------------------+------------------------------------- Changes (by duog): * testcase: => quasiquotation/T13863 * status: new => patch * differential: => Phab:D3677 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jun 27 11:29:40 2017 From: ghc-devs at haskell.org (GHC) Date: Tue, 27 Jun 2017 11:29:40 -0000 Subject: [GHC] #13848: Unexpected order of variable quantification with GADT constructor In-Reply-To: <050.1bdc037c5d3daf9f53281904769def22@haskell.org> References: <050.1bdc037c5d3daf9f53281904769def22@haskell.org> Message-ID: <065.d4a0c8b82805459bb06a7821e6bb08ca@haskell.org> #13848: Unexpected order of variable quantification with GADT constructor -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.1 checker) | Keywords: Resolution: | TypeApplications Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): Well it would take a bit more plumbing, I agree. You'd need to take the `qtkvs` returned by `tcGadtSigType` in `TcTyClsDecls.tcConDecl` and pass it on to `buildDataCon`, which can in turn give them to `mkDataConRep` to use instead of calling `dataConUserType`. I'm not certain that's all, but I think so. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jun 27 11:38:04 2017 From: ghc-devs at haskell.org (GHC) Date: Tue, 27 Jun 2017 11:38:04 -0000 Subject: [GHC] #13873: Adding a SPECIALIZE at a callsite in Main.hs is causing a regression In-Reply-To: <048.468ab4797659afca428d5d90c27d98b1@haskell.org> References: <048.468ab4797659afca428d5d90c27d98b1@haskell.org> Message-ID: <063.206ea301657f5ef830755a10fc711100@haskell.org> #13873: Adding a SPECIALIZE at a callsite in Main.hs is causing a regression -------------------------------------+------------------------------------- Reporter: jberryman | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.2.2 Component: Compiler | Version: 8.2.1-rc2 Resolution: | Keywords: Specialise Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * keywords: => Specialise Comment: As I understand it, you are saying that * adding a SPECIALISE pragma with 8.2 made the the code runs 2x slower Whereas adding the same pragma with 8.0 made the code run 3x faster. (But still not as fast as the slowest version with 8.2.) But it's the bulleted point that is mysterious. Ben please do investigate. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jun 27 11:39:22 2017 From: ghc-devs at haskell.org (GHC) Date: Tue, 27 Jun 2017 11:39:22 -0000 Subject: [GHC] #5928: INLINABLE fails to specialize in presence of simple wrapper In-Reply-To: <044.f94356cf74dc801e8fb7c76a9eaeb24d@haskell.org> References: <044.f94356cf74dc801e8fb7c76a9eaeb24d@haskell.org> Message-ID: <059.bacbcbd8232620a24efee1967ed676b1@haskell.org> #5928: INLINABLE fails to specialize in presence of simple wrapper -------------------------------------+------------------------------------- Reporter: tibbe | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.4.1 Resolution: | Keywords: Inlining, | Specialise Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * keywords: Inlining => Inlining, Specialise -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jun 27 11:40:35 2017 From: ghc-devs at haskell.org (GHC) Date: Tue, 27 Jun 2017 11:40:35 -0000 Subject: [GHC] #7080: Make RULES and SPECIALISE more consistent In-Reply-To: <046.2401df367dbd68df229f7f9e2c5cd6c2@haskell.org> References: <046.2401df367dbd68df229f7f9e2c5cd6c2@haskell.org> Message-ID: <061.1b2d5915438351d1dc22bf9254ee0c24@haskell.org> #7080: Make RULES and SPECIALISE more consistent -------------------------------------+------------------------------------- Reporter: simonpj | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: ⊥ Component: Compiler | Version: 7.4.2 Resolution: | Keywords: Specialise Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * keywords: => Specialise -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jun 27 11:53:01 2017 From: ghc-devs at haskell.org (GHC) Date: Tue, 27 Jun 2017 11:53:01 -0000 Subject: [GHC] #13855: Syntactic sugar to write the recursion in GHC In-Reply-To: <044.4aac734569df8c83745b2d6f55aa7445@haskell.org> References: <044.4aac734569df8c83745b2d6f55aa7445@haskell.org> Message-ID: <059.74a660089f30c378843f3de672409a47@haskell.org> #13855: Syntactic sugar to write the recursion in GHC -------------------------------------+------------------------------------- Reporter: vanto | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by vanto): Wearing the hair shirt\\ A retrospective on Haskell\\ Simon Peyton Jones\\ Microsoft Research, Cambridge\\ POPL’03 meeting\\ In the paragraph named {{{Syntax}}} he said:\\ {{{ Syntactic redundancy ... Haskell's choice: provide multiple ways, and let the programmer decide ... }}} And look what he's saying about the difference between {{{declaration style}}} vs {{{expression style}}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jun 27 12:09:49 2017 From: ghc-devs at haskell.org (GHC) Date: Tue, 27 Jun 2017 12:09:49 -0000 Subject: [GHC] #12912: IO library should not use select() In-Reply-To: <047.2c26cf965e8c4185b06cc1a4540c3c04@haskell.org> References: <047.2c26cf965e8c4185b06cc1a4540c3c04@haskell.org> Message-ID: <062.ee2754f04edc7d83c6134d9c1619fcd7@haskell.org> #12912: IO library should not use select() -------------------------------------+------------------------------------- Reporter: simonmar | Owner: simonmar Type: bug | Status: closed Priority: normal | Milestone: 8.0.2 Component: libraries/base | Version: 8.0.1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #8684, #13525 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by nh2): * related: => #8684, #13525 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jun 27 12:10:46 2017 From: ghc-devs at haskell.org (GHC) Date: Tue, 27 Jun 2017 12:10:46 -0000 Subject: [GHC] #12912: IO library should not use select() In-Reply-To: <047.2c26cf965e8c4185b06cc1a4540c3c04@haskell.org> References: <047.2c26cf965e8c4185b06cc1a4540c3c04@haskell.org> Message-ID: <062.0bde298b3e2eb26440c287ae6a9a7837@haskell.org> #12912: IO library should not use select() -------------------------------------+------------------------------------- Reporter: simonmar | Owner: simonmar Type: bug | Status: closed Priority: normal | Milestone: 8.0.2 Component: libraries/base | Version: 8.0.1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #8684, #13525 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by nh2): This is fixed for GHC 8.2 per #13525 (https://phabricator.haskell.org/rGHCe5732d2a28dfb8a754ee73e124e3558222a543bb) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jun 27 12:16:16 2017 From: ghc-devs at haskell.org (GHC) Date: Tue, 27 Jun 2017 12:16:16 -0000 Subject: [GHC] #8684: hWaitForInput cannot be interrupted by async exceptions on unix In-Reply-To: <042.bed34cc32ec4222496f7d8b921c80c8a@haskell.org> References: <042.bed34cc32ec4222496f7d8b921c80c8a@haskell.org> Message-ID: <057.6ecd2d5cd41f0185d05b6ff8df5d21b9@haskell.org> #8684: hWaitForInput cannot be interrupted by async exceptions on unix -------------------------------------+------------------------------------- Reporter: nh2 | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Core Libraries | Version: 7.6.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: 13525 | Blocking: Related Tickets: #12912, #13525 | Differential Rev(s): Phab:D42 Wiki Page: | -------------------------------------+------------------------------------- Changes (by nh2): * blockedby: => 13525 * related: => #12912, #13525 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jun 27 12:39:23 2017 From: ghc-devs at haskell.org (GHC) Date: Tue, 27 Jun 2017 12:39:23 -0000 Subject: [GHC] #13880: panic initTc: unsolved constraints Message-ID: <044.63308f5431700954c18d18153131bc39@haskell.org> #13880: panic initTc: unsolved constraints -------------------------------------+------------------------------------- Reporter: vanto | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.2 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: Compile-time Unknown/Multiple | crash or panic Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- I'm trying to play with some piece of code in GHCi. Sorry if it's a duplicate bug.\\ {{{ {-# LANGUAGE TemplateHaskell #-} module Testbar where printf :: String -> String printf s = gen (parse s) $(printf "Error: %s at line %d") }}} {{{ Prelude> :l testbar [1 of 1] Compiling Testbar ( testbar.hs, interpreted ) ghc.exe: panic! (the 'impossible' happened) (GHC version 8.0.2 for i386-unknown-mingw32): initTc: unsolved constraints WC {wc_insol = [W] gen_a10Q :: t_a10P[tau:1] (CHoleCan: gen) [W] parse_a10Z :: t_a10Y[tau:1] (CHoleCan: parse)} Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jun 27 13:03:59 2017 From: ghc-devs at haskell.org (GHC) Date: Tue, 27 Jun 2017 13:03:59 -0000 Subject: [GHC] #13876: Check 'pure' method of 'Applicative (WrappedMonad m)' In-Reply-To: <051.5c5537466ef9d8fe586780eff30179d7@haskell.org> References: <051.5c5537466ef9d8fe586780eff30179d7@haskell.org> Message-ID: <066.dffbb947cb2c52ec40915a7250440c07@haskell.org> #13876: Check 'pure' method of 'Applicative (WrappedMonad m)' -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Iceland_jack): To explain: this is not about defining `pure` / `return` differently but rather defining `pure @V3` in terms of `pure @(WrappedMonad V3)` to make use of the methods of `Monad` to define the methods of `Applicative` {{{#!hs pure @V3 @a = coerce (pure @(WrappedMonad V3) @a) = coerce (WrapMonad . pure @V3 @a) = pure @V3 @a }}} With my suggestion this works {{{#!hs pure @V3 @a = coerce (pure @(WrappedMonad V3) @a) = coerce (WrapMonad . return @V3 @a) = return @V3 @a }}} If MRP goes through then I would need a `newtype` wrapped with a `Pointed` & `Monad` constraint to define `Applicative`. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jun 27 13:38:38 2017 From: ghc-devs at haskell.org (GHC) Date: Tue, 27 Jun 2017 13:38:38 -0000 Subject: [GHC] #13337: GHC doesn't think a type is of kind *, despite having evidence for it In-Reply-To: <050.78a537abfa1766ba08f13e5953dd97d8@haskell.org> References: <050.78a537abfa1766ba08f13e5953dd97d8@haskell.org> Message-ID: <065.5c4f38efa23cdc69a6ea7cd08eeb0ddd@haskell.org> #13337: GHC doesn't think a type is of kind *, despite having evidence for it -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: goldfire Type: bug | Status: closed Priority: normal | Milestone: 8.2.1 Component: Compiler (Type | Version: 8.0.2 checker) | Resolution: fixed | Keywords: TypeInType Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: #12677 | Differential Rev(s): Phab:D3315 Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * related: => #12677 Comment: See #12677 for a proper ticket devoted to the `(k ~ Type)` issue. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jun 27 13:39:03 2017 From: ghc-devs at haskell.org (GHC) Date: Tue, 27 Jun 2017 13:39:03 -0000 Subject: [GHC] #12677: Type equality in constraint not used? In-Reply-To: <051.fe74d91fb30a3bb9a0169149567d721f@haskell.org> References: <051.fe74d91fb30a3bb9a0169149567d721f@haskell.org> Message-ID: <066.45e2dbaf6a132179a800a0a0c3bfa7fd@haskell.org> #12677: Type equality in constraint not used? -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #13337 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * cc: RyanGlScott (added) * related: => #13337 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jun 27 13:49:19 2017 From: ghc-devs at haskell.org (GHC) Date: Tue, 27 Jun 2017 13:49:19 -0000 Subject: [GHC] #12087: Inconsistency in GADTs? In-Reply-To: <051.271b252c8ff7e6b4a86908e0694bb2a9@haskell.org> References: <051.271b252c8ff7e6b4a86908e0694bb2a9@haskell.org> Message-ID: <066.185248a9a227b72131438a31c334c19a@haskell.org> #12087: Inconsistency in GADTs? -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: task | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: GADTs Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #11540 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * cc: RyanGlScott (added) * status: closed => new * resolution: invalid => * related: => #11540 Comment: I disagree that this not "valid" Haskell. It's certainly not //standard// Haskell, but I don't see why it ought to be rejected. Perhaps one day after #11540 is fixed, we'll need some extra language extension enabled to use this feature, but I think GHC is more than capable of handling such a thing. For background context: the structure of GADT type signatures are currently validity checked in a rather simple-minded way in [http://git.haskell.org/ghc.git/blob/86abe0e03f6cc2392758d6b45390177d44896113:/compiler/hsSyn/HsDecls.hs#l1189 gadtDeclDetails]. It splits apart a single `forall` with `splitLHsSigmaTy` and checks if the return type is of the form `T a_1 ... a_n`, where `T` is the GADT tycon. But since there's nested sigma types here, GHC mistakenly believes that the return type is `Eq a => a -> F a`, which is bad news. I think it would be possible to tweak this check to accommodate nested foralls, though. Essentially, I think we'd need to create a version of [http://git.haskell.org/ghc.git/blob/86abe0e03f6cc2392758d6b45390177d44896113:/compiler/typecheck/TcType.hs#l1420 tcSplitNestedSigmaTys] that works over `LHsType` instead of `Type`, and replace the use of `splitLHsSigmaTy` with that in `gadtDeclDetails`. Then we'd typecheck `MkF` as if it had the type `forall a. (Ord a, Eq a) => a -> F a`. This isn't exactly what the user //wrote//, but it's equivalent and serviceable. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jun 27 13:49:36 2017 From: ghc-devs at haskell.org (GHC) Date: Tue, 27 Jun 2017 13:49:36 -0000 Subject: [GHC] #12087: Inconsistency in GADTs? In-Reply-To: <051.271b252c8ff7e6b4a86908e0694bb2a9@haskell.org> References: <051.271b252c8ff7e6b4a86908e0694bb2a9@haskell.org> Message-ID: <066.fcf3d6471ca960179de3769f8583c430@haskell.org> #12087: Inconsistency in GADTs? -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: RyanGlScott Type: task | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: GADTs Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #11540 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * owner: (none) => RyanGlScott -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jun 27 13:50:47 2017 From: ghc-devs at haskell.org (GHC) Date: Tue, 27 Jun 2017 13:50:47 -0000 Subject: [GHC] #12018: Equality constraint not available in pattern type signature (GADTs/ScopedTypeVariables) In-Reply-To: <051.6f4adb265ab208b75b739851f1fb480c@haskell.org> References: <051.6f4adb265ab208b75b739851f1fb480c@haskell.org> Message-ID: <066.67248e1673c156e8ef8e09f85df7a390@haskell.org> #12018: Equality constraint not available in pattern type signature (GADTs/ScopedTypeVariables) -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: bug | Status: new Priority: lowest | Milestone: Component: Compiler (Type | Version: 7.10.3 checker) | Keywords: GADTs, Resolution: | ScopedTypeVariables Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * cc: RyanGlScott (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jun 27 13:51:15 2017 From: ghc-devs at haskell.org (GHC) Date: Tue, 27 Jun 2017 13:51:15 -0000 Subject: [GHC] #8033: add AVX register support to llvm calling convention In-Reply-To: <045.7dc8866bbad0b343f7d0cca58aa9a9b3@haskell.org> References: <045.7dc8866bbad0b343f7d0cca58aa9a9b3@haskell.org> Message-ID: <060.91a11d9e23ba300dba8f5d25e8eecbb4@haskell.org> #8033: add AVX register support to llvm calling convention -------------------------------------+------------------------------------- Reporter: carter | Owner: (none) Type: task | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.7 Resolution: | Keywords: SIMD Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): In the interest of unsticking this, I'm going to submit this patch upstream to LLVM tomorrow if there is no objection, {{{#!patch diff --git a/lib/Target/X86/X86CallingConv.td b/lib/Target/X86/X86CallingConv.td index 7d146d050a5..cb6ed24a155 100644 --- a/lib/Target/X86/X86CallingConv.td +++ b/lib/Target/X86/X86CallingConv.td @@ -650,8 +650,16 @@ def CC_X86_64_GHC : CallingConv<[ // Pass in STG registers: F1, F2, F3, F4, D1, D2 CCIfType<[f32, f64, v16i8, v8i16, v4i32, v2i64, v4f32, v2f64], - CCIfSubtarget<"hasSSE1()", - CCAssignToReg<[XMM1, XMM2, XMM3, XMM4, XMM5, XMM6]>>> + CCIfSubtarget<"hasSSE1()", + CCAssignToReg<[XMM1, XMM2, XMM3, XMM4, XMM5, XMM6]>>>, + // AVX + CCIfType<[v32i8, v16i16, v8i32, v4i64, v8f32, v4f64], + CCIfSubtarget<"hasAVX()", + CCAssignToReg<[YMM1, YMM2, YMM3, YMM4, YMM5, YMM6]>>>, + // AVX-512 + CCIfType<[v64i8, v32i16, v16i32, v8i64, v16f32, v8f64], + CCIfSubtarget<"hasAVX512()", + CCAssignToReg<[ZMM1, ZMM2, ZMM3, ZMM4, ZMM5, ZMM6]>>> ]>; def CC_X86_64_HiPE : CallingConv<[ }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jun 27 14:59:39 2017 From: ghc-devs at haskell.org (GHC) Date: Tue, 27 Jun 2017 14:59:39 -0000 Subject: [GHC] #8033: add AVX register support to llvm calling convention In-Reply-To: <045.7dc8866bbad0b343f7d0cca58aa9a9b3@haskell.org> References: <045.7dc8866bbad0b343f7d0cca58aa9a9b3@haskell.org> Message-ID: <060.4661b5a9fe9129f24e11ccb28aad43f5@haskell.org> #8033: add AVX register support to llvm calling convention -------------------------------------+------------------------------------- Reporter: carter | Owner: (none) Type: task | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.7 Resolution: | Keywords: SIMD Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by carter): sounds good to me :) might be worth doing 0-7 to have 8 rather than only 6, but that would require ABI changes on the ghc side, though even this patch does too :) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jun 27 15:17:42 2017 From: ghc-devs at haskell.org (GHC) Date: Tue, 27 Jun 2017 15:17:42 -0000 Subject: [GHC] #13881: Inexplicable error message when using out-of-scope type variable in pattern type signature Message-ID: <050.64fe59f3330624a2ee7d23968276dcc1@haskell.org> #13881: Inexplicable error message when using out-of-scope type variable in pattern type signature -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 (Type checker) | Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: Poor/confusing Unknown/Multiple | error message Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- This code gives an error on any version of GHC since 7.6: {{{#!hs {-# LANGUAGE DataKinds #-} {-# LANGUAGE GADTs #-} {-# LANGUAGE PolyKinds #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE TypeOperators #-} module Bug where data family Sing (a :: k) data instance Sing (z :: [a]) where SNil :: Sing '[] SCons :: Sing x -> Sing xs -> Sing (x ': xs) fl :: forall (l :: [a]). Sing l -> Sing l fl (SNil :: Sing (l :: [y])) = SNil fl (SCons x xs) = SCons x xs }}} {{{ $ /opt/ghc/8.2.1/bin/ghci Bug.hs GHCi, version 8.2.0.20170623: http://www.haskell.org/ghc/ :? for help Loaded GHCi configuration from /home/rgscott/.ghci [1 of 1] Compiling Bug ( Bug.hs, interpreted ) Bug.hs:16:5: error: • The type variable ‘y’ should be bound by the pattern signature ‘Sing l’ but are actually discarded by a type synonym To fix this, expand the type synonym [Note: I hope to lift this restriction in due course] • In the pattern: SNil :: Sing (l :: [y]) In an equation for ‘fl’: fl (SNil :: Sing (l :: [y])) = SNil | 16 | fl (SNil :: Sing (l :: [y])) = SNil | ^^^^^^^^^^^^^^^^^^^^^^^ }}} I can't wrap my head around the error message, though. It complains about a type synonym discarding `y`, but there are no type variables in this program! The //real// source of the issue, the fact that `y` is out of scope (and should actually be `a`), is obscured. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jun 27 15:43:55 2017 From: ghc-devs at haskell.org (GHC) Date: Tue, 27 Jun 2017 15:43:55 -0000 Subject: [GHC] #12018: Equality constraint not available in pattern type signature (GADTs/ScopedTypeVariables) In-Reply-To: <051.6f4adb265ab208b75b739851f1fb480c@haskell.org> References: <051.6f4adb265ab208b75b739851f1fb480c@haskell.org> Message-ID: <066.43d078ba9cf2e132dd3e7c255dc6ed63@haskell.org> #12018: Equality constraint not available in pattern type signature (GADTs/ScopedTypeVariables) -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: bug | Status: new Priority: lowest | Milestone: Component: Compiler (Type | Version: 7.10.3 checker) | Keywords: GADTs, Resolution: | ScopedTypeVariables Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): Replying to [comment:3 simonpj]: > Yes, it is. The type equalities are available only "after" the match. I must admit that I also find this behavior quite counterintuitive. I stumbled into this when I tried typechecking this code: {{{#!hs {-# LANGUAGE DataKinds #-} {-# LANGUAGE GADTs #-} {-# LANGUAGE PolyKinds #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE TypeOperators #-} module Bug where data family Sing (a :: k) data instance Sing (z :: [a]) where SNil :: Sing '[] SCons :: Sing x -> Sing xs -> Sing (x ': xs) fl :: forall (l :: [a]). Sing l -> Sing l fl SNil = SNil fl (SCons (x :: Sing x) (xs :: Sing xs) :: Sing (x ': xs)) = SCons x xs }}} {{{ GHCi, version 8.2.0.20170623: http://www.haskell.org/ghc/ :? for help Loaded GHCi configuration from /home/rgscott/.ghci [1 of 1] Compiling Bug ( Bug.hs, interpreted ) Bug.hs:17:5: error: • Couldn't match type ‘l’ with ‘x : xs’ ‘l’ is a rigid type variable bound by the type signature for: fl :: forall a1 (l :: [a1]). Sing l -> Sing l at Bug.hs:15:1-41 Expected type: Sing l Actual type: Sing (x : xs) • When checking that the pattern signature: Sing (x : xs) fits the type of its context: Sing l In the pattern: SCons (x :: Sing x) (xs :: Sing xs) :: Sing (x : xs) In an equation for ‘fl’: fl (SCons (x :: Sing x) (xs :: Sing xs) :: Sing (x : xs)) = SCons x xs • Relevant bindings include fl :: Sing l -> Sing l (bound at Bug.hs:16:1) | 17 | fl (SCons (x :: Sing x) (xs :: Sing xs) :: Sing (x ': xs)) = SCons x xs | ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ Bug.hs:17:62: error: • Could not deduce: l ~ (x1 : xs1) from the context: (x : xs) ~ (x1 : xs1) bound by a pattern with constructor: SCons :: forall a (x :: a) (xs :: [a]). Sing x -> Sing xs -> Sing (x : xs), in an equation for ‘fl’ at Bug.hs:17:5-39 ‘l’ is a rigid type variable bound by the type signature for: fl :: forall a1 (l :: [a1]). Sing l -> Sing l at Bug.hs:15:1-41 Expected type: Sing l Actual type: Sing (x : xs) • In the expression: SCons x xs In an equation for ‘fl’: fl (SCons (x :: Sing x) (xs :: Sing xs) :: Sing (x : xs)) = SCons x xs • Relevant bindings include xs :: Sing xs (bound at Bug.hs:17:26) x :: Sing x (bound at Bug.hs:17:12) fl :: Sing l -> Sing l (bound at Bug.hs:16:1) | 17 | fl (SCons (x :: Sing x) (xs :: Sing xs) :: Sing (x ': xs)) = SCons x xs | ^^^^^^^^^^ }}} That doesn't typecheck, and yet this does: {{{#!hs fl :: forall (l :: [a]). Sing l -> Sing l fl SNil = SNil fl (SCons (x :: Sing x) (xs :: Sing xs) :: Sing l) = SCons x xs }}} Why not? After all, GHC is smart enough to know how to bind the existentially quantified variables `x` and `xs`, so why can't it conclude that `l ~ x ': xs` from the GADT pattern match? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jun 27 16:04:59 2017 From: ghc-devs at haskell.org (GHC) Date: Tue, 27 Jun 2017 16:04:59 -0000 Subject: [GHC] #602: Warning Suppression In-Reply-To: <047.d851345fc677a304d933040775d25d45@haskell.org> References: <047.d851345fc677a304d933040775d25d45@haskell.org> Message-ID: <062.b1c55812adef84a4b003dcc8d6819d21@haskell.org> #602: Warning Suppression -------------------------------------+------------------------------------- Reporter: simonmar | Owner: (none) Type: task | Status: new Priority: lowest | Milestone: Component: Compiler | Version: None Resolution: None | Keywords: warnings Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple warning at compile-time | Test Case: N/A Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | Design/LocalWarningPragmas | -------------------------------------+------------------------------------- Changes (by ntc2): * cc: ntc2 (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jun 27 16:06:05 2017 From: ghc-devs at haskell.org (GHC) Date: Tue, 27 Jun 2017 16:06:05 -0000 Subject: [GHC] #10150: Suppress orphan instance warning per instance In-Reply-To: <045.dd025a940793eea395715281eec0b7db@haskell.org> References: <045.dd025a940793eea395715281eec0b7db@haskell.org> Message-ID: <060.979b2dcd34ea7b8f28ded20ed6b74f11@haskell.org> #10150: Suppress orphan instance warning per instance -------------------------------------+------------------------------------- Reporter: ezyang | Owner: (none) Type: feature request | Status: new Priority: low | Milestone: Component: Compiler (Type | Version: 7.11 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: #602, #13841 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by ntc2): * cc: ntc2 (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jun 27 16:14:03 2017 From: ghc-devs at haskell.org (GHC) Date: Tue, 27 Jun 2017 16:14:03 -0000 Subject: [GHC] #13882: Template variable unbound in rewrite rule Message-ID: <047.f075bbf62d54c5f19d31d982f96e4ca5@haskell.org> #13882: Template variable unbound in rewrite rule --------------------------------------+--------------------------------- Reporter: achirkin | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.1-rc2 Keywords: | Operating System: Linux Architecture: x86_64 (amd64) | Type of failure: None/Unknown Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: --------------------------------------+--------------------------------- I'm getting GHC panic on `GHC 8.0.1`, `GHC 8.2.1-rc1`, and `GHC 8.2.1-rc2`. I think this error can somehow be related to https://ghc.haskell.org/trac/ghc/ticket/10924 or https://ghc.haskell.org/trac/ghc/ticket/13410 . On all three versions of compiler it builds fine with `-O1` or `-O0`. With `-O2` it crashes with the following error: {{{ [1 of 1] Compiling Numeric.Dimensions.Dim ( Dim.hs, Dim.o ) ghc: panic! (the 'impossible' happened) (GHC version 8.2.0.20170507 for x86_64-unknown-linux): Template variable unbound in rewrite rule Variable: ipv_s1e7 Rule "SC:concatDim0" Rule bndrs: [ipv_s1ee, ipv_s1ed, ipv_s1ef, ys_a19R, ipv_s1e4, ipv_s1e6, sc_s1fF, sc_s1fG, sc_s1fH, sc_s1fI, sc_s1fE, ipv_s1e7] LHS args: [TYPE: (ipv1_s1e6 |> ([Nth:0 (Sym ipv2)])_N), TYPE: ys_a19R, sc_s1fE, :* @ [Nat] @ ys_a19R @ ipv_s1ed @ ipv_s1ee @ ipv1_s1ef @~ (sc_s1fF :: ([Nat] :: *) ~# ([ipv_s1ed] :: *)) @~ (sc_s1fG :: (ys_a19R :: [Nat]) ~# (ConsDim ipv_s1ee ipv2_s1ef :: [ipv1_s1ed])) sc_s1fH sc_s1fI] Actual args: [TYPE: (ipv1_X1eZ |> ([Nth:0 (Sym ipv2)])_N), TYPE: ys_a19R, ipv_s1ea `cast` ((Dim ([Nth:0 (Sym ipv)])_N (Sym (Coh _N ([Nth:0 (Sym ipv)])_N)))_R :: (Dim ipv1_X1eZ :: *) ~R# (Dim (ipv1_X1eZ |> ([Nth:0 (Sym ipv2)])_N) :: *)), :* @ [Nat] @ ys_a19R @ ipv_s1ed @ ipv_s1ee @ ipv1_s1ef @~ (sc_s1fF :: ([Nat] :: *) ~# ([ipv_s1ed] :: *)) @~ (sc_s1fG :: (ys_a19R :: [Nat]) ~# (ConsDim ipv_s1ee ipv2_s1ef :: [ipv1_s1ed])) sc_s1fH sc_s1fI] Call stack: CallStack (from HasCallStack): prettyCurrentCallStack, called at compiler/utils/Outputable.hs:1134:58 in ghc:Outputable callStackDoc, called at compiler/utils/Outputable.hs:1138:37 in ghc:Outputable pprPanic, called at compiler/specialise/Rules.hs:584:19 in ghc:Rules Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug }}} Here is a minimal example I could come up with. Function `concatDim` is what causes the panic. {{{#!hs {-# LANGUAGE DataKinds #-} {-# LANGUAGE GADTs #-} {-# LANGUAGE KindSignatures #-} {-# LANGUAGE PolyKinds #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TypeFamilyDependencies #-} {-# LANGUAGE TypeOperators #-} {-# LANGUAGE UndecidableInstances #-} module Numeric.Dimensions.Dim (Dim (..), concatDim) where import Data.Type.Equality ((:~:)(..)) import GHC.TypeLits (Nat, TypeError, ErrorMessage (..)) import Unsafe.Coerce (unsafeCoerce) -- | Type-level dimensionality data Dim (ns :: k) where D :: Dim '[] (:*) :: forall (n::Nat) (ns::[k]) . Dim n -> Dim ns -> Dim (ConsDim n ns) Dn :: forall (n :: Nat) . Dim (n :: Nat) infixr 5 :* -- | Either known or unknown at compile-time natural number data XNat = XN Nat | N Nat -- | Unknown natural number, known to be not smaller than the given Nat type XN (n::Nat) = 'XN n -- | Known natural number type N (n::Nat) = 'N n -- | List concatenation type family (as :: [k]) ++ (bs :: [k]) :: [k] where (++) '[] bs = bs (++) as '[] = as (++) (a ': as) bs = a ': (as ++ bs) infixr 5 ++ type family Head (xs :: [k]) :: k where Head (x ': xs) = x Head '[] = TypeError ( 'Text "Head -- empty type-level list." ) type family Tail (xs :: [k]) :: [k] where Tail (x ': xs) = xs Tail '[] = TypeError ( 'Text "Tail -- empty type-level list." ) -- | Unify usage of XNat and Nat. -- This is useful in function and type definitions. -- Mainly used in the definition of Dim. type family ConsDim (x :: l) (xs :: [k]) = (ys :: [k]) | ys -> x xs l where ConsDim (x :: Nat) (xs :: [Nat]) = x ': xs ConsDim (x :: Nat) (xs :: [XNat]) = N x ': xs ConsDim (XN m) (xs :: [XNat]) = XN m ': xs concatDim :: forall (xs :: [Nat]) (ys :: [Nat]) . Dim xs -> Dim ys -> Dim (xs ++ ys) concatDim D ys = ys concatDim xs D = xs concatDim (x :* xs) ys = case unsafeCoerce Refl :: (xs ++ ys) :~: (Head xs ': (Tail xs ++ ys)) of Refl -> x :* concatDim xs ys }}} I am a little bit suspicious about `unsafeCoerce Refl`, but it worked in all other places so far. So if you find it not a bug but my incorrect usage of `unsafeCoerce`, please explain me why :) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jun 27 16:22:19 2017 From: ghc-devs at haskell.org (GHC) Date: Tue, 27 Jun 2017 16:22:19 -0000 Subject: [GHC] #12018: Equality constraint not available in pattern type signature (GADTs/ScopedTypeVariables) In-Reply-To: <051.6f4adb265ab208b75b739851f1fb480c@haskell.org> References: <051.6f4adb265ab208b75b739851f1fb480c@haskell.org> Message-ID: <066.1c5ecda79d5759145a3dc82620404e3d@haskell.org> #12018: Equality constraint not available in pattern type signature (GADTs/ScopedTypeVariables) -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: bug | Status: new Priority: lowest | Milestone: Component: Compiler (Type | Version: 7.10.3 checker) | Keywords: GADTs, Resolution: | ScopedTypeVariables Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): > Why not? Because until you have matched on `SCons` we don't have `l ~ x:xs`. I think you are thinking that, because the type signature is "to the right" of the match, you can take advantage of it. But in fact it's more like the type signature encloses the pattern, so it's more like this {{{ fl (Sing (x ': xs) ::: SCons (x :: Sing x) (xs :: Sing xs)) = SCons x xs }}} Here I've used `ty ::: Pat` to put a type sig syntactically "before" the pattern. Now perhaps you would not expect to have matched yet? What about this {{{ g (Just [SCons x xs] :: Maybe [Sing (a ': as)]) = ... }}} presumably you want the pattern to match deeply first. To put it another way, we currently [https://www.haskell.org/onlinereport/haskell2010/haskellch3.html#x8-580003.17 explain pattern matching in the Haskell report] via simple case expressions. Currently we have {{{ case v of ( p::ty -> e1; _ -> e2 } ---> case (v::ty) of { p -> e2; _ -> e2 } }}} But I suppose we could say something like {{{ case v of ( p::ty -> e1; _ -> e2 } ----> case v of { p -> let (v2::ty) = v in e1 ; _ -> e2 } }}} where the type signature is not applied until after the match. I can't say I'm terribly fired up about this. I'm not sure how easy it'd be to match the signature "after" the match. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jun 27 16:25:42 2017 From: ghc-devs at haskell.org (GHC) Date: Tue, 27 Jun 2017 16:25:42 -0000 Subject: [GHC] #13883: T5435_dyn_asm fails with ld.gold Message-ID: <046.0650089fc873411130b9f2d72ad5ad9e@haskell.org> #13883: T5435_dyn_asm fails with ld.gold -------------------------------------+------------------------------------- Reporter: bgamari | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- I'm seeing `T5435_dyn_asm` fail with Phab:D3449 using the gold linker. Specifically, {{{ =====> T5435_dyn_asm(normal) 1 of 1 [0, 0, 0] cd "./rts/T5435_dyn_asm.run" && $MAKE -s --no-print-directory T5435_dyn_asm T5435_dyn_asm failed with ['initArray1', 'initArray2', 'ctors2', 'ctors1', 'success'], see all.T for details *** unexpected failure for T5435_dyn_asm(normal) }}} It seems that the ctor list in `T5435_asm.c` is in order `ctors2,ctors1` as it expects that constructors are run in reverse order, yet somehow with gold the constructors are being run in forward order. I've searched high and low for a document specifying this behavior, but the best I can come up with is GCC's [[https://gcc.gnu.org/onlinedocs/gccint/Initialization.html|internals manual]]. I currently don't have a great answer for why gold flips the order. I suspected that the (enabled by default) `--ctors-in-init-array` flag might have something to do with it, but alas that doesn't appear to be the case. Anyways, given that this most certainly isn't GHC's fault and the order requirements aren't well specified anyways, I'm just going to accept the new ordering. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jun 27 16:25:51 2017 From: ghc-devs at haskell.org (GHC) Date: Tue, 27 Jun 2017 16:25:51 -0000 Subject: [GHC] #13883: T5435_dyn_asm fails with ld.gold In-Reply-To: <046.0650089fc873411130b9f2d72ad5ad9e@haskell.org> References: <046.0650089fc873411130b9f2d72ad5ad9e@haskell.org> Message-ID: <061.8ea4bf7adbd49c58b6131f27ff60f118@haskell.org> #13883: T5435_dyn_asm fails with ld.gold -------------------------------------+------------------------------------- Reporter: bgamari | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => closed * resolution: => fixed -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jun 27 16:30:59 2017 From: ghc-devs at haskell.org (GHC) Date: Tue, 27 Jun 2017 16:30:59 -0000 Subject: [GHC] #13884: To an automatic compilation of file-header LANGUAGE pragmas in GHC. Message-ID: <044.5438e0b55f2f96ccdf324b161ad363cb@haskell.org> #13884: To an automatic compilation of file-header LANGUAGE pragmas in GHC. -------------------------------------+------------------------------------- Reporter: vanto | Owner: (none) Type: feature | Status: new request | Priority: normal | Milestone: Component: Compiler | Version: 8.0.2 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: Other Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- I wrote this little piece of code to show that the compiler could very well execute the pragma by itself without being ordered to do so.\\ {{{ module Testfoo where import Language.Haskell.TH.Lib import Data.Kind tup = $(tupE $ take 4 $ cycle [ [| "hi" |] , [| 5 |] ]) data T = MkT (forall a. [a] -> [a]) answer_read = show (read @Int "3") data Foo (a :: Type) (b :: Type) where MkFoo :: (a ~ Int, b ~ Char) => Foo a b data family Song (a :: k) }}} By compiling the code without the Pragmas, GHC responds:\\ * 1) c:\Testghc>ghc testfoo.hs [1 of 1] Compiling Testfoo ( testfoo.hs, testfoo.o ) testfoo.hs:13:7: error: parse error on input `$' Perhaps you intended to use TemplateHaskell\\ * 2) c:\Testghc>ghc testfoo.hs [1 of 1] Compiling Testfoo ( testfoo.hs, testfoo.o ) testfoo.hs:15:23: error: Illegal symbol '.' in type Perhaps you intended to use {{{RankNTypes}}} or a similar language extension to enable explicit-forall syntax: forall .\\ * 3) c:\Testghc>ghc testfoo.hs [1 of 1] Compiling Testfoo ( testfoo.hs, testfoo.o ) testfoo.hs:19:16: error: Illegal kind signature: `Type' Perhaps you intended to use KindSignatures In the data type declaration for `Foo' testfoo.hs:19:28: error: Illegal kind signature: `Type' Perhaps you intended to use KindSignatures In the data type declaration for `Foo' testfoo.hs:22:1: error: Unexpected kind variable `k' Perhaps you intended to use {{{PolyKinds}}} In the declaration for type family `Song' testfoo.hs:22:24: error: Illegal kind signature: `k' Perhaps you intended to use KindSignatures In the declaration for type family `Song'\\ * 4) c:\Testghc>ghc testfoo.hs [1 of 1] Compiling Testfoo ( testfoo.hs, testfoo.o ) testfoo.hs:18:21: error: Pattern syntax in expression context: read at Int Did you mean to enable {{{TypeApplications}}}?\\ * 5) c:\Testghc>ghc testfoo.hs [1 of 1] Compiling Testfoo ( testfoo.hs, testfoo.o ) testfoo.hs:20:1: error: * Illegal generalised algebraic data declaration for `Foo' (Use {{{GADTs}}} to allow GADTs) * In the data declaration for `Foo'\\ * 6) c:\Testghc>ghc testfoo.hs [1 of 1] Compiling Testfoo ( testfoo.hs, testfoo.o ) testfoo.hs:23:1: error: * Illegal family declaration for `Song' Use {{{TypeFamilies}}} to allow indexed type families * In the data family declaration for `Song'\\ * 7) c:\Testghc>ghc testfoo.hs [1 of 1] Compiling Testfoo ( testfoo.hs, testfoo.o ) c:\Testghc>\\ Here is the code once completed. {{{ {-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE RankNTypes #-} {-# LANGUAGE PolyKinds #-} {-# LANGUAGE TypeApplications #-} {-# LANGUAGE GADTs #-} {-# LANGUAGE TypeFamilies #-} module Testfoo where import Language.Haskell.TH.Lib import Data.Kind tup = $(tupE $ take 4 $ cycle [ [| "hi" |] , [| 5 |] ]) data T = MkT (forall a. [a] -> [a]) answer_read = show (read @Int "3") data Foo (a :: Type) (b :: Type) where MkFoo :: (a ~ Int, b ~ Char) => Foo a b data family Song (a :: k) }}} As you may notice, GHC suggests the appropriate pragma.\\ If we add manually in the code the Pragmas one after the other and we arrive at the end, the code is fully compiled without error.\\ The compiler could do this alone.\\ We could test it using a "-auto" option on the compiler command line.\\ This is a start to the compiler automation technology, what do you think of that? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jun 27 16:53:36 2017 From: ghc-devs at haskell.org (GHC) Date: Tue, 27 Jun 2017 16:53:36 -0000 Subject: [GHC] #13880: panic initTc: unsolved constraints In-Reply-To: <044.63308f5431700954c18d18153131bc39@haskell.org> References: <044.63308f5431700954c18d18153131bc39@haskell.org> Message-ID: <059.e8188de0f6b851e71ebf07fb4da473d6@haskell.org> #13880: panic initTc: unsolved constraints -------------------------------------+------------------------------------- Reporter: vanto | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.2.1 Component: Compiler | Version: 8.0.2 Resolution: duplicate | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: #13106 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => closed * resolution: => duplicate * related: => #13106 * milestone: => 8.2.1 @@ -4,1 +4,1 @@ - {{{ + {{{#!hs New description: I'm trying to play with some piece of code in GHCi. Sorry if it's a duplicate bug.\\ {{{#!hs {-# LANGUAGE TemplateHaskell #-} module Testbar where printf :: String -> String printf s = gen (parse s) $(printf "Error: %s at line %d") }}} {{{ Prelude> :l testbar [1 of 1] Compiling Testbar ( testbar.hs, interpreted ) ghc.exe: panic! (the 'impossible' happened) (GHC version 8.0.2 for i386-unknown-mingw32): initTc: unsolved constraints WC {wc_insol = [W] gen_a10Q :: t_a10P[tau:1] (CHoleCan: gen) [W] parse_a10Z :: t_a10Y[tau:1] (CHoleCan: parse)} Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug }}} -- Comment: I believe this is a duplicate of #13106. I get a reasonable error with 8.2. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jun 27 17:10:25 2017 From: ghc-devs at haskell.org (GHC) Date: Tue, 27 Jun 2017 17:10:25 -0000 Subject: [GHC] #12018: Equality constraint not available in pattern type signature (GADTs/ScopedTypeVariables) In-Reply-To: <051.6f4adb265ab208b75b739851f1fb480c@haskell.org> References: <051.6f4adb265ab208b75b739851f1fb480c@haskell.org> Message-ID: <066.1282b577d75b94f084e8edfac857f84d@haskell.org> #12018: Equality constraint not available in pattern type signature (GADTs/ScopedTypeVariables) -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: bug | Status: new Priority: lowest | Milestone: Component: Compiler (Type | Version: 7.10.3 checker) | Keywords: GADTs, Resolution: | ScopedTypeVariables Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): Replying to [comment:6 simonpj]: > Because until you have matched on `SCons` we don't have `l ~ x:xs`. I think you are thinking that, because the type signature is "to the right" of the match, you can take advantage of it. The position of the type signature has nothing to do with my confusion. I'm confused because it's been drilled into my skull that the act of pattern matching on a GADT constructor in a case changes the typing rules (or, more precisely, it introduces new given constraints) for that case. The fact that I can use these given constraints for the types of subpatterns of `SCons ...`, but for the type of the `SCons ...` pattern itself, feels oddly disjointed. To highlight the strangeness of this further, you can do what I desire simply by adding another `case` expression: {{{#!hs fl :: forall (l :: [a]). Sing l -> Sing l fl SNil = SNil fl a@(SCons (x :: Sing x) (xs :: Sing xs)) = case a of (a :: Sing (x ': xs)) -> SCons x xs }}} I'd rather cut out of the middleman and just put that `Sing (x ': xs)` type directly on the `SCons ...` pattern. > To put it another way, we currently [https://www.haskell.org/onlinereport/haskell2010/haskellch3.html#x8-580003.17 explain pattern matching in the Haskell report] via simple case expressions. Currently we have > {{{ > case v of ( p::ty -> e1; _ -> e2 } > ---> > case (v::ty) of { p -> e2; _ -> e2 } > }}} I'm not sure where you got that rule from in the link you provided. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jun 27 17:34:37 2017 From: ghc-devs at haskell.org (GHC) Date: Tue, 27 Jun 2017 17:34:37 -0000 Subject: [GHC] #8281: The impossible happened: primRepToFFIType In-Reply-To: <044.47e20917996e473150de04c1ce1afc0b@haskell.org> References: <044.47e20917996e473150de04c1ce1afc0b@haskell.org> Message-ID: <059.35b5ce498d6d21f559cdc21b19b7eee4@haskell.org> #8281: The impossible happened: primRepToFFIType -------------------------------------+------------------------------------- Reporter: tibbe | Owner: (none) Type: bug | Status: patch Priority: high | Milestone: 8.4.1 Component: Compiler | Version: 7.6.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3619 Wiki Page: | -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"9ef909db5ed3dc45fc1acdb608ad3f1896362966/ghc" 9ef909d/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="9ef909db5ed3dc45fc1acdb608ad3f1896362966" Allow bytecode interpreter to make unsafe foreign calls Reviewers: austin, hvr, erikd, simonmar Reviewed By: simonmar Subscribers: rwbarton, thomie GHC Trac Issues: #8281, #13730. Differential Revision: https://phabricator.haskell.org/D3619 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jun 27 17:34:37 2017 From: ghc-devs at haskell.org (GHC) Date: Tue, 27 Jun 2017 17:34:37 -0000 Subject: [GHC] #13871: GHC panic in 8.2 only: typeIsTypeable(Coercion) In-Reply-To: <050.f1a0fc44d1ac315eabed1b0be5437302@haskell.org> References: <050.f1a0fc44d1ac315eabed1b0be5437302@haskell.org> Message-ID: <065.e82f3439ee8e370a671a91f6f45e61e7@haskell.org> #13871: GHC panic in 8.2 only: typeIsTypeable(Coercion) -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: bgamari Type: bug | Status: patch Priority: high | Milestone: 8.2.1 Component: Compiler (Type | Version: 8.2.1-rc2 checker) | Keywords: TypeInType, Resolution: | Typeable Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Compile-time | Test Case: crash or panic | typecheck/should_compile/T13871 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3671, Wiki Page: | Phab:D3672 -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"134652542923e432bffb9fafe87893d785a17aae/ghc" 13465254/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="134652542923e432bffb9fafe87893d785a17aae" typecheck: Consider types containing coercions non-Typeable This was previously a panic and caused #13871. I believe just saying these types simply aren't Typeable should be correct. Test Plan: Validate, check `T13871` Reviewers: goldfire, austin Subscribers: rwbarton, thomie, RyanGlScott GHC Trac Issues: #13871 Differential Revision: https://phabricator.haskell.org/D3672 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jun 27 17:34:37 2017 From: ghc-devs at haskell.org (GHC) Date: Tue, 27 Jun 2017 17:34:37 -0000 Subject: [GHC] #13730: Running GLUT code in GHCi yields NSInternalInconsistencyException In-Reply-To: <050.f6283f68597bb13f67605132a145b9f1@haskell.org> References: <050.f6283f68597bb13f67605132a145b9f1@haskell.org> Message-ID: <065.f5824d5f09e020d3a85be650332af04c@haskell.org> #13730: Running GLUT code in GHCi yields NSInternalInconsistencyException --------------------------------+---------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: GHCi | Version: 8.0.2 Resolution: | Keywords: Operating System: MacOS X | Architecture: Unknown/Multiple Type of failure: GHCi crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | --------------------------------+---------------------------------------- Comment (by Ben Gamari ): In [changeset:"9ef909db5ed3dc45fc1acdb608ad3f1896362966/ghc" 9ef909d/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="9ef909db5ed3dc45fc1acdb608ad3f1896362966" Allow bytecode interpreter to make unsafe foreign calls Reviewers: austin, hvr, erikd, simonmar Reviewed By: simonmar Subscribers: rwbarton, thomie GHC Trac Issues: #8281, #13730. Differential Revision: https://phabricator.haskell.org/D3619 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jun 27 17:34:37 2017 From: ghc-devs at haskell.org (GHC) Date: Tue, 27 Jun 2017 17:34:37 -0000 Subject: [GHC] #13871: GHC panic in 8.2 only: typeIsTypeable(Coercion) In-Reply-To: <050.f1a0fc44d1ac315eabed1b0be5437302@haskell.org> References: <050.f1a0fc44d1ac315eabed1b0be5437302@haskell.org> Message-ID: <065.bb94d9a9da61307c0f209ca5e7de80b1@haskell.org> #13871: GHC panic in 8.2 only: typeIsTypeable(Coercion) -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: bgamari Type: bug | Status: patch Priority: high | Milestone: 8.2.1 Component: Compiler (Type | Version: 8.2.1-rc2 checker) | Keywords: TypeInType, Resolution: | Typeable Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Compile-time | Test Case: crash or panic | typecheck/should_compile/T13871 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3671, Wiki Page: | Phab:D3672 -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"12a3c394b12e5e07314895e6c419f4f4031ad3a9/ghc" 12a3c39/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="12a3c394b12e5e07314895e6c419f4f4031ad3a9" testsuite: Add broken test for #13871 Test Plan: Validate Reviewers: austin Subscribers: rwbarton, thomie, RyanGlScott GHC Trac Issues: #13871 Differential Revision: https://phabricator.haskell.org/D3671 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jun 27 17:34:37 2017 From: ghc-devs at haskell.org (GHC) Date: Tue, 27 Jun 2017 17:34:37 -0000 Subject: =?utf-8?b?UmU6IFtHSENdICMxMzYxNTogTm9uZGV0ZXJtaW5pc20gaW4g4oCY?= =?utf-8?q?pure=E2=80=99_function_w/_parallel_evaluation_=26_memo?= =?utf-8?q?_combinators?= In-Reply-To: <044.57733831351687fff6258688df1f42f7@haskell.org> References: <044.57733831351687fff6258688df1f42f7@haskell.org> Message-ID: <059.14133e9c14003d77451881e8023827ae@haskell.org> #13615: Nondeterminism in ‘pure’ function w/ parallel evaluation & memo combinators -------------------------------------+------------------------------------- Reporter: pacak | Owner: bgamari Type: bug | Status: new Priority: highest | Milestone: 8.2.1 Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"1e471265c1ea9b2c4e9709adc182c36d0635f071/ghc" 1e47126/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="1e471265c1ea9b2c4e9709adc182c36d0635f071" rts: Clarify whitehole logic in threadPaused Previously we would look at the indirectee field of a WHITEHOLE object. However, WHITEHOLE isn't a sort of indirection and therefore has no indirectee field. I encountered this while investigating #13615, although it doesn't fix that bug. Test Plan: Validate Reviewers: simonmar, austin, erikd Subscribers: rwbarton, thomie GHC Trac Issues: #13615 Differential Revision: https://phabricator.haskell.org/D3674 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jun 27 17:34:37 2017 From: ghc-devs at haskell.org (GHC) Date: Tue, 27 Jun 2017 17:34:37 -0000 Subject: [GHC] #13594: Typechecker behavior w.r.t. BangPatterns and nested foralls has changed in 8.2 In-Reply-To: <050.d768cbcd7afd3c7633840a8a13d3da1c@haskell.org> References: <050.d768cbcd7afd3c7633840a8a13d3da1c@haskell.org> Message-ID: <065.a213fa1b94ce162968a02b6d3f4a9394@haskell.org> #13594: Typechecker behavior w.r.t. BangPatterns and nested foralls has changed in 8.2 -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: bgamari Type: bug | Status: patch Priority: high | Milestone: 8.2.1 Component: Compiler (Type | Version: 8.2.1-rc2 checker) | Keywords: BangPatterns, Resolution: | RankNTypes Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3661 Wiki Page: | -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"6567c815135e93f8550d526f81d13f31c0cd92b6/ghc" 6567c81/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="6567c815135e93f8550d526f81d13f31c0cd92b6" Treat banged bindings as FunBinds This is another attempt at resolving #13594 by treating strict variable binds as FunBinds instead of PatBinds (as suggested in comment:1). Test Plan: Validate Reviewers: austin, alanz Subscribers: rwbarton, thomie, mpickering GHC Trac Issues: #13594 Differential Revision: https://phabricator.haskell.org/D3670 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jun 27 17:39:10 2017 From: ghc-devs at haskell.org (GHC) Date: Tue, 27 Jun 2017 17:39:10 -0000 Subject: [GHC] #13871: GHC panic in 8.2 only: typeIsTypeable(Coercion) In-Reply-To: <050.f1a0fc44d1ac315eabed1b0be5437302@haskell.org> References: <050.f1a0fc44d1ac315eabed1b0be5437302@haskell.org> Message-ID: <065.cdd96f9e5839cbf58bf43ff73a74ce50@haskell.org> #13871: GHC panic in 8.2 only: typeIsTypeable(Coercion) -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: bgamari Type: bug | Status: merge Priority: high | Milestone: 8.2.1 Component: Compiler (Type | Version: 8.2.1-rc2 checker) | Keywords: TypeInType, Resolution: | Typeable Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Compile-time | Test Case: crash or panic | typecheck/should_compile/T13871 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3671, Wiki Page: | Phab:D3672 -------------------------------------+------------------------------------- Changes (by bgamari): * status: patch => merge -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jun 27 17:40:59 2017 From: ghc-devs at haskell.org (GHC) Date: Tue, 27 Jun 2017 17:40:59 -0000 Subject: [GHC] #13594: Typechecker behavior w.r.t. BangPatterns and nested foralls has changed in 8.2 In-Reply-To: <050.d768cbcd7afd3c7633840a8a13d3da1c@haskell.org> References: <050.d768cbcd7afd3c7633840a8a13d3da1c@haskell.org> Message-ID: <065.148a05c2030888fa6ea87cfb372f0ba8@haskell.org> #13594: Typechecker behavior w.r.t. BangPatterns and nested foralls has changed in 8.2 -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: bgamari Type: bug | Status: merge Priority: high | Milestone: 8.2.1 Component: Compiler (Type | Version: 8.2.1-rc2 checker) | Keywords: BangPatterns, Resolution: | RankNTypes Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3661 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: patch => merge -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jun 27 18:48:21 2017 From: ghc-devs at haskell.org (GHC) Date: Tue, 27 Jun 2017 18:48:21 -0000 Subject: [GHC] #13884: To an automatic compilation of file-header LANGUAGE pragmas in GHC. In-Reply-To: <044.5438e0b55f2f96ccdf324b161ad363cb@haskell.org> References: <044.5438e0b55f2f96ccdf324b161ad363cb@haskell.org> Message-ID: <059.8ed19c5ce1801160df18017896ab24ce@haskell.org> #13884: To an automatic compilation of file-header LANGUAGE pragmas in GHC. -------------------------------------+------------------------------------- Reporter: vanto | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Other | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Description changed by bgamari: @@ -4,1 +4,1 @@ - {{{ + {{{#!hs @@ -20,1 +20,1 @@ - By compiling the code without the Pragmas, GHC responds:\\ + By compiling the code without the Pragmas, GHC responds: @@ -22,0 +22,1 @@ + {{{ @@ -81,0 +82,1 @@ + }}} @@ -84,1 +86,1 @@ - {{{ + {{{#!hs New description: I wrote this little piece of code to show that the compiler could very well execute the pragma by itself without being ordered to do so.\\ {{{#!hs module Testfoo where import Language.Haskell.TH.Lib import Data.Kind tup = $(tupE $ take 4 $ cycle [ [| "hi" |] , [| 5 |] ]) data T = MkT (forall a. [a] -> [a]) answer_read = show (read @Int "3") data Foo (a :: Type) (b :: Type) where MkFoo :: (a ~ Int, b ~ Char) => Foo a b data family Song (a :: k) }}} By compiling the code without the Pragmas, GHC responds: {{{ * 1) c:\Testghc>ghc testfoo.hs [1 of 1] Compiling Testfoo ( testfoo.hs, testfoo.o ) testfoo.hs:13:7: error: parse error on input `$' Perhaps you intended to use TemplateHaskell\\ * 2) c:\Testghc>ghc testfoo.hs [1 of 1] Compiling Testfoo ( testfoo.hs, testfoo.o ) testfoo.hs:15:23: error: Illegal symbol '.' in type Perhaps you intended to use {{{RankNTypes}}} or a similar language extension to enable explicit-forall syntax: forall .\\ * 3) c:\Testghc>ghc testfoo.hs [1 of 1] Compiling Testfoo ( testfoo.hs, testfoo.o ) testfoo.hs:19:16: error: Illegal kind signature: `Type' Perhaps you intended to use KindSignatures In the data type declaration for `Foo' testfoo.hs:19:28: error: Illegal kind signature: `Type' Perhaps you intended to use KindSignatures In the data type declaration for `Foo' testfoo.hs:22:1: error: Unexpected kind variable `k' Perhaps you intended to use {{{PolyKinds}}} In the declaration for type family `Song' testfoo.hs:22:24: error: Illegal kind signature: `k' Perhaps you intended to use KindSignatures In the declaration for type family `Song'\\ * 4) c:\Testghc>ghc testfoo.hs [1 of 1] Compiling Testfoo ( testfoo.hs, testfoo.o ) testfoo.hs:18:21: error: Pattern syntax in expression context: read at Int Did you mean to enable {{{TypeApplications}}}?\\ * 5) c:\Testghc>ghc testfoo.hs [1 of 1] Compiling Testfoo ( testfoo.hs, testfoo.o ) testfoo.hs:20:1: error: * Illegal generalised algebraic data declaration for `Foo' (Use {{{GADTs}}} to allow GADTs) * In the data declaration for `Foo'\\ * 6) c:\Testghc>ghc testfoo.hs [1 of 1] Compiling Testfoo ( testfoo.hs, testfoo.o ) testfoo.hs:23:1: error: * Illegal family declaration for `Song' Use {{{TypeFamilies}}} to allow indexed type families * In the data family declaration for `Song'\\ * 7) c:\Testghc>ghc testfoo.hs [1 of 1] Compiling Testfoo ( testfoo.hs, testfoo.o ) c:\Testghc>\\ }}} Here is the code once completed. {{{#!hs {-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE RankNTypes #-} {-# LANGUAGE PolyKinds #-} {-# LANGUAGE TypeApplications #-} {-# LANGUAGE GADTs #-} {-# LANGUAGE TypeFamilies #-} module Testfoo where import Language.Haskell.TH.Lib import Data.Kind tup = $(tupE $ take 4 $ cycle [ [| "hi" |] , [| 5 |] ]) data T = MkT (forall a. [a] -> [a]) answer_read = show (read @Int "3") data Foo (a :: Type) (b :: Type) where MkFoo :: (a ~ Int, b ~ Char) => Foo a b data family Song (a :: k) }}} As you may notice, GHC suggests the appropriate pragma.\\ If we add manually in the code the Pragmas one after the other and we arrive at the end, the code is fully compiled without error.\\ The compiler could do this alone.\\ We could test it using a "-auto" option on the compiler command line.\\ This is a start to the compiler automation technology, what do you think of that? -- -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jun 27 19:01:44 2017 From: ghc-devs at haskell.org (GHC) Date: Tue, 27 Jun 2017 19:01:44 -0000 Subject: [GHC] #13884: To an automatic compilation of file-header LANGUAGE pragmas in GHC. In-Reply-To: <044.5438e0b55f2f96ccdf324b161ad363cb@haskell.org> References: <044.5438e0b55f2f96ccdf324b161ad363cb@haskell.org> Message-ID: <059.f9805497133c88b2b0e2a7f67a21dd78@haskell.org> #13884: To an automatic compilation of file-header LANGUAGE pragmas in GHC. -------------------------------------+------------------------------------- Reporter: vanto | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Other | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): Making pragmas implicit, even with a flag, is a slippery slope that I don't believe we want to head down. GHC's pragma suggestions are just that: suggestions. They are the result of heuristics and by no means are these heuristics always correct. I suspect that making the compiler's behavior conditional on these heuristics would at best result in some very confusing error messages. There are many ways that wee might want to reduce the cost of pragmas. Even today you can enable them with project-level granularity in your Cabal file. Moreover, IDE tooling quickly approaching the point where it can help the user make pragma changes. In the future we might also consider adding a few more "meta-extensions" (e.g. `-XDependentHaskell`) capturing sets of commonly needed pragmas. Does this help? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jun 27 19:41:40 2017 From: ghc-devs at haskell.org (GHC) Date: Tue, 27 Jun 2017 19:41:40 -0000 Subject: [GHC] #11990: Custom Type Error not getting triggered in the nested Type function call In-Reply-To: <047.cd64e02ac6207e6c5247bec38dfaa3ba@haskell.org> References: <047.cd64e02ac6207e6c5247bec38dfaa3ba@haskell.org> Message-ID: <062.d7a5747dba68d839c59273b34fb77d20@haskell.org> #11990: Custom Type Error not getting triggered in the nested Type function call -------------------------------------+------------------------------------- Reporter: magesh.b | Owner: diatchki Type: bug | Status: closed Priority: normal | Milestone: 8.0.2 Component: Compiler | Version: 8.0.1-rc3 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by tstr): Hi, for the example blow I'm wondering why GHC 8.0.2 fails on "TestError" with a custom type error, but at the same time happily accepts "NestedTypeError"? Is that the expected behavior of GHC? Many thanks for your help, Thomas {{{ {-# LANGUAGE DataKinds #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE TypeOperators #-} {-# LANGUAGE UndecidableInstances #-} module CustomErrorBug where import GHC.TypeLits -- Works as expected and makes GHC complain: type TestError = TypeError (Text "Top level custom errors work!") -- GHC 8.0.2 is absolutely happy with this: type family NestedError (x::Symbol) where NestedError x = TypeError (Text "NestedError: " :<>: ShowType x) type TestNestedError = NestedError "Why are nested custom errors not propagated?" }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jun 27 19:45:01 2017 From: ghc-devs at haskell.org (GHC) Date: Tue, 27 Jun 2017 19:45:01 -0000 Subject: [GHC] #11990: Custom Type Error not getting triggered in the nested Type function call In-Reply-To: <047.cd64e02ac6207e6c5247bec38dfaa3ba@haskell.org> References: <047.cd64e02ac6207e6c5247bec38dfaa3ba@haskell.org> Message-ID: <062.a17145e16814591daab8f569b0aa89a6@haskell.org> #11990: Custom Type Error not getting triggered in the nested Type function call -------------------------------------+------------------------------------- Reporter: magesh.b | Owner: diatchki Type: bug | Status: closed Priority: normal | Milestone: 8.0.2 Component: Compiler | Version: 8.0.1-rc3 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by tstr): * cc: tstr (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jun 27 19:58:14 2017 From: ghc-devs at haskell.org (GHC) Date: Tue, 27 Jun 2017 19:58:14 -0000 Subject: [GHC] #13311: Audit shady uses of tcSplitSigmaTy In-Reply-To: <050.72458ab96a239fb6dc8ceaeb2c02afab@haskell.org> References: <050.72458ab96a239fb6dc8ceaeb2c02afab@haskell.org> Message-ID: <065.ed2dccbe251298124c12bd5712aee246@haskell.org> #13311: Audit shady uses of tcSplitSigmaTy -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: RyanGlScott Type: task | Status: patch Priority: normal | Milestone: 8.4.1 Component: Compiler (Type | Version: 8.1 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3678 Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * status: new => patch * differential: => Phab:D3678 Comment: Interestingly, I can't produce the "unlifted bindings"-related panic anymore with the GHC 8.2 branch. But the other issue is simple enough to fix: Phab:D3678. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jun 27 20:47:40 2017 From: ghc-devs at haskell.org (GHC) Date: Tue, 27 Jun 2017 20:47:40 -0000 Subject: [GHC] #13885: Template Haskell doesn't freshen GADT kind variables properly when imported from another package Message-ID: <050.316bfca35535b28b80cdb6a4e733201d@haskell.org> #13885: Template Haskell doesn't freshen GADT kind variables properly when imported from another package -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Template | Version: 8.0.1 Haskell | Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: Incorrect result Unknown/Multiple | at runtime Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- A simple way to illustrate this bug is with this code: {{{#!hs {-# LANGUAGE GADTs #-} {-# LANGUAGE PolyKinds #-} {-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE TypeOperators #-} module Foo where import qualified Data.Type.Equality as DTE ((:~:)) import Language.Haskell.TH data a :~: b where Refl :: a :~: a $(return []) main :: IO () main = do putStrLn "Imported\n-----" putStrLn $(reify ''(DTE.:~:) >>= stringE . pprint) putStrLn "-----\n\nLocally defined\n-----" putStrLn $(reify ''(:~:) >>= stringE . pprint) putStrLn "-----" }}} Here, I'm pretty-printing the reified Template Haskell information about two datatypes: one that is imported from another package (`base`), and another that is defined locally. Aside from their definition sites, they are otherwise identical. However, when reifying them with Template Haskell, there is another distinction one can observe: {{{ $ /opt/ghc/8.2.1/bin/runghc Foo.hs Imported ----- data Data.Type.Equality.:~: (a_0 :: k_1) (b_2 :: k_1) where Data.Type.Equality.Refl :: forall (k_1 :: *) (a_0 :: k_1) . Data.Type.Equality.:~: a_0 a_0 ----- Locally defined ----- data Foo.:~: (a_0 :: k_1) (b_2 :: k_1) where Foo.Refl :: forall (k_3 :: *) (a_4 :: k_3) . Foo.:~: a_4 a_4 ----- }}} The locally defined information looks fine, but the one imported from `base` is suspicious. Namely, the `k_1` variable is used both in the datatype head and in the quantified variables for the constructor! To confirm this, you can print out more verbose info with `show` instead of `pprint`: {{{ Imported ----- TyConI (DataD [] Data.Type.Equality.:~: [KindedTV a_6989586621679026781 (VarT k_6989586621679026780),KindedTV b_6989586621679026782 (VarT k_6989586621679026780)] Nothing [ForallC [KindedTV k_6989586621679026780 StarT,KindedTV a_6989586621679026781 (VarT k_6989586621679026780)] [] (GadtC [Data.Type.Equality.Refl] [] (AppT (AppT (ConT Data.Type.Equality.:~:) (VarT a_6989586621679026781)) (VarT a_6989586621679026781)))] []) ----- Locally defined ----- TyConI (DataD [] Foo.:~: [KindedTV a_6989586621679016094 (VarT k_6989586621679016098),KindedTV b_6989586621679016095 (VarT k_6989586621679016098)] Nothing [ForallC [KindedTV k_6989586621679016108 StarT,KindedTV a_6989586621679016096 (VarT k_6989586621679016108)] [] (GadtC [Foo.Refl] [] (AppT (AppT (ConT Foo.:~:) (VarT a_6989586621679016096)) (VarT a_6989586621679016096)))] []) ----- }}} Sure enough, the variable `k_6989586621679026780` is used in both places. I would expect this not to happen, since the two sets of variables are scoped differently, and in practice, I have to work around this by freshening the type variables for the constructor, which is annoying. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jun 27 20:59:32 2017 From: ghc-devs at haskell.org (GHC) Date: Tue, 27 Jun 2017 20:59:32 -0000 Subject: [GHC] #13886: GHC panic when using GHC plugins Message-ID: <048.4e65bf02b6c4ff69cd509bbe731fe7ea@haskell.org> #13886: GHC panic when using GHC plugins -------------------------------------+------------------------------------- Reporter: Darwin226 | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.2 Keywords: | Operating System: Windows Architecture: x86_64 | Type of failure: Compile-time (amd64) | crash or panic Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- I'm running GHC 8.0.2 on Windows 10. At first I was playing around with making my own type-checker plugin and I kept getting {{{#!hs ghc.EXE: panic! (the 'impossible' happened) (GHC version 8.0.2 for x86_64-unknown-mingw32): Static flags have not been initialised! Please call GHC.parseStaticFlags early enough. }}} on certain function calls (things like printing Docs). But now on an unrelated project I tried using the dump-core plugin and I'm getting the same error. The minimal example I can produce is simply {{{#!hs module Main where main = return () }}} compiled with `stack exec ghc -- -fplugin=DumpCore PluginTest.hs` (or I'm guessing equivalently `ghc -fplugin=DumpCore PluginTest.hs`) Make sure to install the dump-core package first. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jun 27 21:01:20 2017 From: ghc-devs at haskell.org (GHC) Date: Tue, 27 Jun 2017 21:01:20 -0000 Subject: [GHC] #13885: Template Haskell doesn't freshen GADT type variables properly (was: Template Haskell doesn't freshen GADT kind variables properly when imported from another package) In-Reply-To: <050.316bfca35535b28b80cdb6a4e733201d@haskell.org> References: <050.316bfca35535b28b80cdb6a4e733201d@haskell.org> Message-ID: <065.f202649a4b2ec33f023a0faa182e5b5f@haskell.org> #13885: Template Haskell doesn't freshen GADT type variables properly -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): Actually, it's not just kind variables, and you don't need to necessarily import them from another package. Another way to trigger this problem is to use `ExistentialQuantification` instead of `GADTs`: {{{#!hs {-# LANGUAGE ExistentialQuantification #-} {-# LANGUAGE PolyKinds #-} {-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE TypeOperators #-} module Foo where import Language.Haskell.TH data a :~: b = a ~ b => Refl $(return []) main :: IO () main = putStrLn $(reify ''(:~:) >>= stringE . pprint) }}} {{{ $ /opt/ghc/8.2.1/bin/runghc Foo.hs data Foo.:~: (a_0 :: k_1) (b_2 :: k_1) where Foo.Refl :: forall (k_1 :: *) (a_0 :: k_1) (b_2 :: k_1) . Data.Type.Equality.~ a_0 b_2 => Foo.:~: a_0 b_2 }}} Now we are shadowing both the type variables `a_0` and `b_2`, as well as the kind variable `k_1`. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jun 27 21:03:41 2017 From: ghc-devs at haskell.org (GHC) Date: Tue, 27 Jun 2017 21:03:41 -0000 Subject: [GHC] #12018: Equality constraint not available in pattern type signature (GADTs/ScopedTypeVariables) In-Reply-To: <051.6f4adb265ab208b75b739851f1fb480c@haskell.org> References: <051.6f4adb265ab208b75b739851f1fb480c@haskell.org> Message-ID: <066.dedc0c0e266aa0904c9281f3a0de030f@haskell.org> #12018: Equality constraint not available in pattern type signature (GADTs/ScopedTypeVariables) -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: bug | Status: new Priority: lowest | Milestone: Component: Compiler (Type | Version: 7.10.3 checker) | Keywords: GADTs, Resolution: | ScopedTypeVariables Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): > it's been drilled into my skull that the act of pattern matching on a GADT constructor in a case changes the typing rules Correct -- but it only brings those constraints into scope in ''parts'' of the program. For example {{{ data T a where TBool :: TBool TOther :: T a f :: a -> T a -> Int f True TBool = 3 -- Rejected g :: T a -> a -> Int g TBool True = 3 -- Accepted }}} `f` is rejected because pattern matching goes left-to-right and outside- in. So when we meet the `True` we are not in the scope of `a~Bool`. But `g` is fine. In the case of a type signature, when matching `(p :: ty)` we first meet `ty` and only then match `p`. You want to match `p` and only then match `ty` with the refined type of the pattern. But currently `ty` signature may restrict the type of the pattern; I'm not sure that would be so easy if the signature was only matched after matching the pattern. In short, I don't see an easy, compositional way to give you what you want. Maybe someone else does. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jun 27 21:10:27 2017 From: ghc-devs at haskell.org (GHC) Date: Tue, 27 Jun 2017 21:10:27 -0000 Subject: [GHC] #12018: Equality constraint not available in pattern type signature (GADTs/ScopedTypeVariables) In-Reply-To: <051.6f4adb265ab208b75b739851f1fb480c@haskell.org> References: <051.6f4adb265ab208b75b739851f1fb480c@haskell.org> Message-ID: <066.35410a7e1f371427579a83cc5c92944d@haskell.org> #12018: Equality constraint not available in pattern type signature (GADTs/ScopedTypeVariables) -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: bug | Status: new Priority: lowest | Milestone: Component: Compiler (Type | Version: 7.10.3 checker) | Keywords: GADTs, Resolution: | ScopedTypeVariables Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): Ah, thank you for those examples, Simon. I was imaging GADT pattern- matching to be a sort of "whole-case" operation, but that is clearly not the case, as `f` demonstrates. So I think I'm barking up the entirely wrong tree with what I was requesting in comment:5. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jun 27 21:13:06 2017 From: ghc-devs at haskell.org (GHC) Date: Tue, 27 Jun 2017 21:13:06 -0000 Subject: [GHC] #13887: Template Haskell pretty-printer doesn't parenthesize infix datatype names in data declarations Message-ID: <050.e6ef0eaaad5555a490c4013a48ebaae7@haskell.org> #13887: Template Haskell pretty-printer doesn't parenthesize infix datatype names in data declarations -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Template | Version: 8.0.1 Haskell | Keywords: newcomer | Operating System: Unknown/Multiple Architecture: | Type of failure: Incorrect result Unknown/Multiple | at runtime Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- If you run this program: {{{#!hs {-# LANGUAGE ExistentialQuantification #-} {-# LANGUAGE PolyKinds #-} {-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE TypeOperators #-} module Foo where import Language.Haskell.TH main :: IO () main = do putStrLn $([d| data a :~: b where Refl1 :: a :~: a |] >>= stringE . pprint) putStrLn $([d| data a :~~: b = a ~ b => Refl2 |] >>= stringE . pprint) }}} {{{ $ /opt/ghc/8.2.1/bin/runghc Foo.hs data :~:_0 a_1 b_2 where Refl1_3 :: :~:_0 a_4 a_4 data :~~:_0 a_1 b_2 = a_1 ~ b_2 => Refl2_3 }}} It'll print the output incorrectly. Those infix names `:~:` and `:~~:` ought to be surrounded by parentheses, since they're used in prefix position. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jun 27 21:16:58 2017 From: ghc-devs at haskell.org (GHC) Date: Tue, 27 Jun 2017 21:16:58 -0000 Subject: [GHC] #13886: GHC panic when using GHC plugins In-Reply-To: <048.4e65bf02b6c4ff69cd509bbe731fe7ea@haskell.org> References: <048.4e65bf02b6c4ff69cd509bbe731fe7ea@haskell.org> Message-ID: <063.f3f471a0a08b93e5a4595daab3e203af@haskell.org> #13886: GHC panic when using GHC plugins -------------------------------------+------------------------------------- Reporter: Darwin226 | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.2 Resolution: | Keywords: Operating System: Windows | Architecture: x86_64 Type of failure: Compile-time | (amd64) crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): It's possible that this is a duplicate of #10301, which claims to be fixed in GHC 8.2.1. Is it possible to test your program with 8.2.1-rc2? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jun 27 21:40:12 2017 From: ghc-devs at haskell.org (GHC) Date: Tue, 27 Jun 2017 21:40:12 -0000 Subject: [GHC] #13730: Running GLUT code in GHCi yields NSInternalInconsistencyException In-Reply-To: <050.f6283f68597bb13f67605132a145b9f1@haskell.org> References: <050.f6283f68597bb13f67605132a145b9f1@haskell.org> Message-ID: <065.c5d2ac5be9234a755de4e7ef95c5600a@haskell.org> #13730: Running GLUT code in GHCi yields NSInternalInconsistencyException --------------------------------+---------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.4.1 Component: GHCi | Version: 8.0.2 Resolution: fixed | Keywords: Operating System: MacOS X | Architecture: Unknown/Multiple Type of failure: GHCi crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | --------------------------------+---------------------------------------- Changes (by bgamari): * status: new => closed * resolution: => fixed * milestone: => 8.4.1 Comment: I can confirm that comment:8 fixes the example. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jun 27 21:46:28 2017 From: ghc-devs at haskell.org (GHC) Date: Tue, 27 Jun 2017 21:46:28 -0000 Subject: [GHC] #13810: Gold linker fails In-Reply-To: <045.174b108f34b20d346eba46d31b44114b@haskell.org> References: <045.174b108f34b20d346eba46d31b44114b@haskell.org> Message-ID: <060.901a3ed45b2473b592fc31e4e32d6070@haskell.org> #13810: Gold linker fails ---------------------------------+---------------------------------------- Reporter: ksaric | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.2.1 Component: Compiler | Version: 8.0.1 Resolution: wontfix | Keywords: linker Operating System: Linux | Architecture: Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | ---------------------------------+---------------------------------------- Changes (by bgamari): * status: new => closed * resolution: => wontfix * milestone: => 8.2.1 Comment: We have decided that we will merge the fix #13541 for 8.2.1, so there should be no need to pass ld flags like this in the future. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jun 27 21:55:09 2017 From: ghc-devs at haskell.org (GHC) Date: Tue, 27 Jun 2017 21:55:09 -0000 Subject: [GHC] #13886: GHC panic when using GHC plugins In-Reply-To: <048.4e65bf02b6c4ff69cd509bbe731fe7ea@haskell.org> References: <048.4e65bf02b6c4ff69cd509bbe731fe7ea@haskell.org> Message-ID: <063.53b291e20b95b798fdb35ca806c0ddf6@haskell.org> #13886: GHC panic when using GHC plugins -------------------------------------+------------------------------------- Reporter: Darwin226 | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.2 Resolution: | Keywords: Operating System: Windows | Architecture: x86_64 Type of failure: Compile-time | (amd64) crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Darwin226): I would but it seems this https://ghc.haskell.org/trac/ghc/ticket/13560 is blocking me. Is there a newer binary that I can use? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jun 27 22:00:35 2017 From: ghc-devs at haskell.org (GHC) Date: Tue, 27 Jun 2017 22:00:35 -0000 Subject: [GHC] #13886: GHC panic when using GHC plugins In-Reply-To: <048.4e65bf02b6c4ff69cd509bbe731fe7ea@haskell.org> References: <048.4e65bf02b6c4ff69cd509bbe731fe7ea@haskell.org> Message-ID: <063.5625d190caae7efa65dac888fd89d222@haskell.org> #13886: GHC panic when using GHC plugins -------------------------------------+------------------------------------- Reporter: Darwin226 | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.2 Resolution: | Keywords: Operating System: Windows | Architecture: x86_64 Type of failure: Compile-time | (amd64) crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): I believe 8.2.1-rc2 https://downloads.haskell.org/~ghc/8.2.1-rc2/ should have this fixed. If not, you can work around this yourself by editing `\lib\settings` and changing `"C compiler command"` yourself. (I forget what exactly you should change it to, but a working copy of GHC should have a correct value set for this.) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jun 27 23:15:41 2017 From: ghc-devs at haskell.org (GHC) Date: Tue, 27 Jun 2017 23:15:41 -0000 Subject: [GHC] #13885: Template Haskell doesn't freshen GADT type variables properly In-Reply-To: <050.316bfca35535b28b80cdb6a4e733201d@haskell.org> References: <050.316bfca35535b28b80cdb6a4e733201d@haskell.org> Message-ID: <065.fc56515e953bd65a6a2203568ed4e438@haskell.org> #13885: Template Haskell doesn't freshen GADT type variables properly -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): Why does this matter? If I write {{{ data T a b where MkT :: [a] -> b -> x -> T x a }}} that's absolutely fine. The 'a' and 'b' in the `MkT` signature have nothing to do with the variables in the head. The latter do not scope over the constructors. Right? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jun 28 02:24:49 2017 From: ghc-devs at haskell.org (GHC) Date: Wed, 28 Jun 2017 02:24:49 -0000 Subject: [GHC] #8281: The impossible happened: primRepToFFIType In-Reply-To: <044.47e20917996e473150de04c1ce1afc0b@haskell.org> References: <044.47e20917996e473150de04c1ce1afc0b@haskell.org> Message-ID: <059.75442c3f614b702431a89d6878179974@haskell.org> #8281: The impossible happened: primRepToFFIType -------------------------------------+------------------------------------- Reporter: tibbe | Owner: (none) Type: bug | Status: patch Priority: high | Milestone: 8.4.1 Component: Compiler | Version: 7.6.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3619 Wiki Page: | -------------------------------------+------------------------------------- Comment (by winter): Thank you! I suggest to add some document in manual as well. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jun 28 03:43:00 2017 From: ghc-devs at haskell.org (GHC) Date: Wed, 28 Jun 2017 03:43:00 -0000 Subject: [GHC] #13885: Template Haskell doesn't freshen GADT type variables properly In-Reply-To: <050.316bfca35535b28b80cdb6a4e733201d@haskell.org> References: <050.316bfca35535b28b80cdb6a4e733201d@haskell.org> Message-ID: <065.14ca70ce0016c8170482a40d7848e745@haskell.org> #13885: Template Haskell doesn't freshen GADT type variables properly -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): Sure, I know that //conceptually//, they have different scopes. I would just find it convenient to have different uniques for differently scoped variables in the reified Template Haskell output, as it would greatly simplify some code that I'm developing that benefits from the assumption that TH ASTs are fully uniquified. It's a minor thing, but it would be a definite quality-of-life improvement. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jun 28 04:05:25 2017 From: ghc-devs at haskell.org (GHC) Date: Wed, 28 Jun 2017 04:05:25 -0000 Subject: [GHC] #13877: GHC panic: No skolem info: k2 In-Reply-To: <050.85aac3d842c3e1851a442a13f59ce985@haskell.org> References: <050.85aac3d842c3e1851a442a13f59ce985@haskell.org> Message-ID: <065.4f3fa4b76379f0b37b3c1587cbc0bf7b@haskell.org> #13877: GHC panic: No skolem info: k2 -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.1 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): Here's another occurrence of this panic I found when writing similar code: {{{#!hs {-# LANGUAGE GADTs #-} {-# LANGUAGE RankNTypes #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TypeApplications #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE TypeInType #-} module Bug where import Data.Kind data family Sing (a :: k) data WeirdList :: Type -> Type where WeirdNil :: WeirdList a WeirdCons :: a -> WeirdList (WeirdList a) -> WeirdList a data instance Sing (z :: WeirdList a) where SWeirdNil :: Sing WeirdNil SWeirdCons :: Sing w -> Sing wws -> Sing (WeirdCons w wws) elimWeirdList :: forall (a :: Type) (wl :: WeirdList a) (p :: forall (x :: Type). x -> WeirdList x -> Type). Sing wl -> (forall (y :: Type). p _ WeirdNil) -> (forall (z :: Type) (x :: z) (xs :: WeirdList (WeirdList z)). Sing x -> Sing xs -> p _ xs -> p _ (WeirdCons x xs)) -> p _ wl elimWeirdList SWeirdNil pWeirdNil _ = pWeirdNil elimWeirdList (SWeirdCons (x :: Sing (x :: z)) (xs :: Sing (xs :: WeirdList (WeirdList z)))) pWeirdNil pWeirdCons = pWeirdCons @z @x @xs x xs (elimWeirdList @(WeirdList z) @xs @p xs pWeirdNil pWeirdCons) }}} {{{ $ /opt/ghc/8.2.1/bin/ghci Bug.hs GHCi, version 8.2.0.20170623: http://www.haskell.org/ghc/ :? for help Loaded GHCi configuration from /home/rgscott/.ghci [1 of 1] Compiling Bug ( Bug.hs, interpreted ) Bug.hs:21:18: error: • The kind of variable ‘wl1’, namely ‘WeirdList a1’, depends on variable ‘a1’ from an inner scope Perhaps bind ‘wl1’ sometime after binding ‘a1’ • In the type signature: elimWeirdList :: forall (a :: Type) (wl :: WeirdList a) (p :: forall (x :: Type). x -> WeirdList x -> Type). Sing wl -> (forall (y :: Type). p _ WeirdNil) -> (forall (z :: Type) (x :: z) (xs :: WeirdList (WeirdList z)). Sing x -> Sing xs -> p _ xs -> p _ (WeirdCons x xs)) -> p _ wl | 21 | elimWeirdList :: forall (a :: Type) (wl :: WeirdList a) | ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^... Bug.hs:24:41: error: • Found type wildcard ‘_’ standing for ‘w0’ Where: ‘w0’ is an ambiguous type variable ‘x0’ is an ambiguous type variable To use the inferred type, enable PartialTypeSignatures • In the type signature: elimWeirdList :: forall (a :: Type) (wl :: WeirdList a) (p :: forall (x :: Type). x -> WeirdList x -> Type). Sing wl -> (forall (y :: Type). p _ WeirdNil) -> (forall (z :: Type) (x :: z) (xs :: WeirdList (WeirdList z)). Sing x -> Sing xs -> p _ xs -> p _ (WeirdCons x xs)) -> p _ wl | 24 | -> (forall (y :: Type). p _ WeirdNil) | ^ Bug.hs:26:44: error:ghc: panic! (the 'impossible' happened) (GHC version 8.2.0.20170623 for x86_64-unknown-linux): No skolem info: z_a1sY[sk:2] Call stack: CallStack (from HasCallStack): prettyCurrentCallStack, called at compiler/utils/Outputable.hs:1133:58 in ghc:Outputable callStackDoc, called at compiler/utils/Outputable.hs:1137:37 in ghc:Outputable pprPanic, called at compiler/typecheck/TcErrors.hs:2653:5 in ghc:TcErrors Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jun 28 05:25:01 2017 From: ghc-devs at haskell.org (GHC) Date: Wed, 28 Jun 2017 05:25:01 -0000 Subject: [GHC] #13882: Template variable unbound in rewrite rule In-Reply-To: <047.f075bbf62d54c5f19d31d982f96e4ca5@haskell.org> References: <047.f075bbf62d54c5f19d31d982f96e4ca5@haskell.org> Message-ID: <062.0a8898dc2ca10ab52b1ad07fd6392279@haskell.org> #13882: Template variable unbound in rewrite rule -------------------------------------+------------------------------------- Reporter: achirkin | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.1-rc2 Resolution: | Keywords: Operating System: Linux | Architecture: x86_64 Type of failure: Compile-time | (amd64) crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by achirkin): * failure: None/Unknown => Compile-time crash or panic -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jun 28 07:17:00 2017 From: ghc-devs at haskell.org (GHC) Date: Wed, 28 Jun 2017 07:17:00 -0000 Subject: [GHC] #13810: Gold linker fails In-Reply-To: <045.174b108f34b20d346eba46d31b44114b@haskell.org> References: <045.174b108f34b20d346eba46d31b44114b@haskell.org> Message-ID: <060.b17747af75ec01e4cce30d48006dd8d3@haskell.org> #13810: Gold linker fails ---------------------------------+---------------------------------------- Reporter: ksaric | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.2.1 Component: Compiler | Version: 8.0.1 Resolution: wontfix | Keywords: linker Operating System: Linux | Architecture: Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | ---------------------------------+---------------------------------------- Comment (by ksaric): Ok, great, thanks! -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jun 28 07:25:35 2017 From: ghc-devs at haskell.org (GHC) Date: Wed, 28 Jun 2017 07:25:35 -0000 Subject: [GHC] #13884: To an automatic compilation of file-header LANGUAGE pragmas in GHC. In-Reply-To: <044.5438e0b55f2f96ccdf324b161ad363cb@haskell.org> References: <044.5438e0b55f2f96ccdf324b161ad363cb@haskell.org> Message-ID: <059.c821b3213e3fad2ef30bedb6931211de@haskell.org> #13884: To an automatic compilation of file-header LANGUAGE pragmas in GHC. -------------------------------------+------------------------------------- Reporter: vanto | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Other | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by vanto): Replying to bgamari\\ >>I suspect that making the compiler's behavior conditional on these heuristics >>would at best result in some very confusing error messages.\\ Maybe or maybe not. GHC messages should not be underestimated. Here he answered well.\\ Take a look at this other example.\\ {{{ module Testfoo2 where import Data.Kind data Foo (a :: Type) (b :: Type) where MkFoo :: (a ~ Int, b ~ Char) => Foo a b }}} GHC responds\\ {{{ Prelude> :l testfoo2 [1 of 1] Compiling Testfoo2 ( testfoo2.hs, interpreted ) testfoo2.hs:10:16: error: Illegal kind signature: `Type' Perhaps you intended to use KindSignatures In the data type declaration for `Foo' testfoo2.hs:10:28: error: Illegal kind signature: `Type' Perhaps you intended to use KindSignatures In the data type declaration for `Foo' Failed, modules loaded: none. Prelude> :r [1 of 1] Compiling Testfoo2 ( testfoo2.hs, interpreted ) testfoo2.hs:11:1: error: * Illegal generalised algebraic data declaration for `Foo' (Use GADTs to allow GADTs) * In the data declaration for `Foo' Failed, modules loaded: none. Prelude> :r [1 of 1] Compiling Testfoo2 ( testfoo2.hs, interpreted ) Ok, modules loaded: Testfoo2. }}} If the second function is added {{{ data family Song (a :: k) }}} and that we start again, GHC respond:\\ {{{ *Testfoo2> :l testfoo2 [1 of 1] Compiling Testfoo2 ( testfoo2.hs, interpreted ) testfoo2.hs:13:16: error: Illegal kind signature: `Type' Perhaps you intended to use KindSignatures In the data type declaration for `Foo' testfoo2.hs:13:28: error: Illegal kind signature: `Type' Perhaps you intended to use KindSignatures In the data type declaration for `Foo' testfoo2.hs:16:1: error: Unexpected kind variable `k' Perhaps you intended to use PolyKinds In the declaration for type family `Song' testfoo2.hs:16:24: error: Illegal kind signature: `k' Perhaps you intended to use KindSignatures In the declaration for type family `Song' Failed, modules loaded: none. Prelude> :r [1 of 1] Compiling Testfoo2 ( testfoo2.hs, interpreted ) testfoo2.hs:16:1: error: Unexpected kind variable `k' Perhaps you intended to use PolyKinds In the declaration for type family `Song' Failed, modules loaded: none. Prelude> :r [1 of 1] Compiling Testfoo2 ( testfoo2.hs, interpreted ) testfoo2.hs:13:1: error: * Illegal generalised algebraic data declaration for `Foo' (Use GADTs to allow GADTs) * In the data declaration for `Foo' Failed, modules loaded: none. Prelude> :r [1 of 1] Compiling Testfoo2 ( testfoo2.hs, interpreted ) testfoo2.hs:16:1: error: * Illegal family declaration for `Song' Use TypeFamilies to allow indexed type families * In the data family declaration for `Song' Failed, modules loaded: none. Prelude> :r [1 of 1] Compiling Testfoo2 ( testfoo2.hs, interpreted ) Ok, modules loaded: Testfoo2. *Testfoo2> :r [1 of 1] Compiling Testfoo2 ( testfoo2.hs, interpreted ) Ok, modules loaded: Testfoo2. }}} If you look closer you can even remove the pragma {{{ {- # LANGUAGE KindSignatures # -} }}} And the program still compiles well. And GHC did it all alone without my help.\\ I think that has the merit of being studied. You have to be enthusiastic about doing that. Maybe in twenty years someone will code that? They will be compilers worthy of the twenty-first century. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jun 28 07:52:59 2017 From: ghc-devs at haskell.org (GHC) Date: Wed, 28 Jun 2017 07:52:59 -0000 Subject: [GHC] #13886: GHC panic when using GHC plugins In-Reply-To: <048.4e65bf02b6c4ff69cd509bbe731fe7ea@haskell.org> References: <048.4e65bf02b6c4ff69cd509bbe731fe7ea@haskell.org> Message-ID: <063.525b96c424ea178de31920596fae9b2e@haskell.org> #13886: GHC panic when using GHC plugins -------------------------------------+------------------------------------- Reporter: Darwin226 | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.2 Resolution: | Keywords: Operating System: Windows | Architecture: x86_64 Type of failure: Compile-time | (amd64) crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Darwin226): Got it installed but dump-core doesn't work with the newer base... I'll try playing around with my type-checker plugin and see if that works -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jun 28 08:00:33 2017 From: ghc-devs at haskell.org (GHC) Date: Wed, 28 Jun 2017 08:00:33 -0000 Subject: [GHC] #13886: GHC panic when using GHC plugins In-Reply-To: <048.4e65bf02b6c4ff69cd509bbe731fe7ea@haskell.org> References: <048.4e65bf02b6c4ff69cd509bbe731fe7ea@haskell.org> Message-ID: <063.099153f60951f5623de88358736db053@haskell.org> #13886: GHC panic when using GHC plugins -------------------------------------+------------------------------------- Reporter: Darwin226 | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.2 Resolution: | Keywords: Operating System: Windows | Architecture: x86_64 Type of failure: Compile-time | (amd64) crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by mpickering): It does work if you pass the `--allow-newer` flag. I have been using it recently. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jun 28 08:38:35 2017 From: ghc-devs at haskell.org (GHC) Date: Wed, 28 Jun 2017 08:38:35 -0000 Subject: [GHC] #13882: Template variable unbound in rewrite rule In-Reply-To: <047.f075bbf62d54c5f19d31d982f96e4ca5@haskell.org> References: <047.f075bbf62d54c5f19d31d982f96e4ca5@haskell.org> Message-ID: <062.f3787731fc24d27973a1222d17c715d0@haskell.org> #13882: Template variable unbound in rewrite rule -------------------------------------+------------------------------------- Reporter: achirkin | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.1-rc2 Resolution: | Keywords: Operating System: Linux | Architecture: x86_64 Type of failure: Compile-time | (amd64) crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- @@ -149,0 +149,23 @@ + + UPDATE 28.06.2017: + Interestingly, the two variants below compile fine with `-O2`: + {{{#!hs + concatDim :: forall (xs :: [Nat]) (ys :: [Nat]) . Dim xs -> Dim ys -> Dim + (xs ++ ys) + concatDim D ys = ys + concatDim xs D = xs + concatDim (x :* xs) ys = case unsafeCoerce Refl :: (xs ++ ys) :~: (Head xs + ': (Tail xs ++ ys)) of + Refl -> x :* concatDim xs ys + {-# NOINLINE concatDim #-} + }}} + + {{{#!hs + concatDim :: forall (xs :: [Nat]) (ys :: [Nat]) . Dim xs -> Dim ys -> Dim + (xs ++ ys) + concatDim D ys = ys + concatDim xs D = xs + concatDim (x :* xs) ys = case unsafeCoerce Refl :: (xs ++ ys) :~: (Head xs + ': (Tail xs ++ ys)) of + Refl -> x :* concatDim (undefined :: Dim (Tail xs)) ys + }}} New description: I'm getting GHC panic on `GHC 8.0.1`, `GHC 8.2.1-rc1`, and `GHC 8.2.1-rc2`. I think this error can somehow be related to https://ghc.haskell.org/trac/ghc/ticket/10924 or https://ghc.haskell.org/trac/ghc/ticket/13410 . On all three versions of compiler it builds fine with `-O1` or `-O0`. With `-O2` it crashes with the following error: {{{ [1 of 1] Compiling Numeric.Dimensions.Dim ( Dim.hs, Dim.o ) ghc: panic! (the 'impossible' happened) (GHC version 8.2.0.20170507 for x86_64-unknown-linux): Template variable unbound in rewrite rule Variable: ipv_s1e7 Rule "SC:concatDim0" Rule bndrs: [ipv_s1ee, ipv_s1ed, ipv_s1ef, ys_a19R, ipv_s1e4, ipv_s1e6, sc_s1fF, sc_s1fG, sc_s1fH, sc_s1fI, sc_s1fE, ipv_s1e7] LHS args: [TYPE: (ipv1_s1e6 |> ([Nth:0 (Sym ipv2)])_N), TYPE: ys_a19R, sc_s1fE, :* @ [Nat] @ ys_a19R @ ipv_s1ed @ ipv_s1ee @ ipv1_s1ef @~ (sc_s1fF :: ([Nat] :: *) ~# ([ipv_s1ed] :: *)) @~ (sc_s1fG :: (ys_a19R :: [Nat]) ~# (ConsDim ipv_s1ee ipv2_s1ef :: [ipv1_s1ed])) sc_s1fH sc_s1fI] Actual args: [TYPE: (ipv1_X1eZ |> ([Nth:0 (Sym ipv2)])_N), TYPE: ys_a19R, ipv_s1ea `cast` ((Dim ([Nth:0 (Sym ipv)])_N (Sym (Coh _N ([Nth:0 (Sym ipv)])_N)))_R :: (Dim ipv1_X1eZ :: *) ~R# (Dim (ipv1_X1eZ |> ([Nth:0 (Sym ipv2)])_N) :: *)), :* @ [Nat] @ ys_a19R @ ipv_s1ed @ ipv_s1ee @ ipv1_s1ef @~ (sc_s1fF :: ([Nat] :: *) ~# ([ipv_s1ed] :: *)) @~ (sc_s1fG :: (ys_a19R :: [Nat]) ~# (ConsDim ipv_s1ee ipv2_s1ef :: [ipv1_s1ed])) sc_s1fH sc_s1fI] Call stack: CallStack (from HasCallStack): prettyCurrentCallStack, called at compiler/utils/Outputable.hs:1134:58 in ghc:Outputable callStackDoc, called at compiler/utils/Outputable.hs:1138:37 in ghc:Outputable pprPanic, called at compiler/specialise/Rules.hs:584:19 in ghc:Rules Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug }}} Here is a minimal example I could come up with. Function `concatDim` is what causes the panic. {{{#!hs {-# LANGUAGE DataKinds #-} {-# LANGUAGE GADTs #-} {-# LANGUAGE KindSignatures #-} {-# LANGUAGE PolyKinds #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TypeFamilyDependencies #-} {-# LANGUAGE TypeOperators #-} {-# LANGUAGE UndecidableInstances #-} module Numeric.Dimensions.Dim (Dim (..), concatDim) where import Data.Type.Equality ((:~:)(..)) import GHC.TypeLits (Nat, TypeError, ErrorMessage (..)) import Unsafe.Coerce (unsafeCoerce) -- | Type-level dimensionality data Dim (ns :: k) where D :: Dim '[] (:*) :: forall (n::Nat) (ns::[k]) . Dim n -> Dim ns -> Dim (ConsDim n ns) Dn :: forall (n :: Nat) . Dim (n :: Nat) infixr 5 :* -- | Either known or unknown at compile-time natural number data XNat = XN Nat | N Nat -- | Unknown natural number, known to be not smaller than the given Nat type XN (n::Nat) = 'XN n -- | Known natural number type N (n::Nat) = 'N n -- | List concatenation type family (as :: [k]) ++ (bs :: [k]) :: [k] where (++) '[] bs = bs (++) as '[] = as (++) (a ': as) bs = a ': (as ++ bs) infixr 5 ++ type family Head (xs :: [k]) :: k where Head (x ': xs) = x Head '[] = TypeError ( 'Text "Head -- empty type-level list." ) type family Tail (xs :: [k]) :: [k] where Tail (x ': xs) = xs Tail '[] = TypeError ( 'Text "Tail -- empty type-level list." ) -- | Unify usage of XNat and Nat. -- This is useful in function and type definitions. -- Mainly used in the definition of Dim. type family ConsDim (x :: l) (xs :: [k]) = (ys :: [k]) | ys -> x xs l where ConsDim (x :: Nat) (xs :: [Nat]) = x ': xs ConsDim (x :: Nat) (xs :: [XNat]) = N x ': xs ConsDim (XN m) (xs :: [XNat]) = XN m ': xs concatDim :: forall (xs :: [Nat]) (ys :: [Nat]) . Dim xs -> Dim ys -> Dim (xs ++ ys) concatDim D ys = ys concatDim xs D = xs concatDim (x :* xs) ys = case unsafeCoerce Refl :: (xs ++ ys) :~: (Head xs ': (Tail xs ++ ys)) of Refl -> x :* concatDim xs ys }}} I am a little bit suspicious about `unsafeCoerce Refl`, but it worked in all other places so far. So if you find it not a bug but my incorrect usage of `unsafeCoerce`, please explain me why :) UPDATE 28.06.2017: Interestingly, the two variants below compile fine with `-O2`: {{{#!hs concatDim :: forall (xs :: [Nat]) (ys :: [Nat]) . Dim xs -> Dim ys -> Dim (xs ++ ys) concatDim D ys = ys concatDim xs D = xs concatDim (x :* xs) ys = case unsafeCoerce Refl :: (xs ++ ys) :~: (Head xs ': (Tail xs ++ ys)) of Refl -> x :* concatDim xs ys {-# NOINLINE concatDim #-} }}} {{{#!hs concatDim :: forall (xs :: [Nat]) (ys :: [Nat]) . Dim xs -> Dim ys -> Dim (xs ++ ys) concatDim D ys = ys concatDim xs D = xs concatDim (x :* xs) ys = case unsafeCoerce Refl :: (xs ++ ys) :~: (Head xs ': (Tail xs ++ ys)) of Refl -> x :* concatDim (undefined :: Dim (Tail xs)) ys }}} -- Comment (by achirkin): After some experimenting added two examples illustrating the strange optimizer behaviour. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jun 28 09:06:03 2017 From: ghc-devs at haskell.org (GHC) Date: Wed, 28 Jun 2017 09:06:03 -0000 Subject: [GHC] #13884: To an automatic compilation of file-header LANGUAGE pragmas in GHC. In-Reply-To: <044.5438e0b55f2f96ccdf324b161ad363cb@haskell.org> References: <044.5438e0b55f2f96ccdf324b161ad363cb@haskell.org> Message-ID: <059.2671838eacaf4c23be2043eed3ddf142@haskell.org> #13884: To an automatic compilation of file-header LANGUAGE pragmas in GHC. -------------------------------------+------------------------------------- Reporter: vanto | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Other | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by vanto): Replying to bgamari (2)\\ I forgot to say this. Because GHC will have to make several go and return to find the right solution in order to use it for compilation, I suggest using the backtracking algorithm found in the Prolog language. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jun 28 09:06:06 2017 From: ghc-devs at haskell.org (GHC) Date: Wed, 28 Jun 2017 09:06:06 -0000 Subject: [GHC] #12494: Implementation of setenv in base incorrectly claims empty environment variable not supported on Windows In-Reply-To: <045.fd6c657ae3b3eb1c0db68ee27fdabe97@haskell.org> References: <045.fd6c657ae3b3eb1c0db68ee27fdabe97@haskell.org> Message-ID: <060.04362a8cf9d8391b2ca3717e230c6e1a@haskell.org> #12494: Implementation of setenv in base incorrectly claims empty environment variable not supported on Windows -------------------------------------+------------------------------------- Reporter: ezyang | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: libraries/base | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by habibalamin): Here's how Ruby handles empty environment variables on Windows — https://github.com/ruby/ruby/commit/2982c5289210c02120172bf631270858681d031d #diff-1f049b4f9a6a39cee9cf18b2dc85f637R3147. Are we agreed on the course of action? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jun 28 10:33:33 2017 From: ghc-devs at haskell.org (GHC) Date: Wed, 28 Jun 2017 10:33:33 -0000 Subject: [GHC] #13888: GHC 8.0.2 panics when trying a simple snippet involving Parsec Message-ID: <048.209ad257f958bd88adecc8c8a6266ee6@haskell.org> #13888: GHC 8.0.2 panics when trying a simple snippet involving Parsec -------------------------------------+------------------------------------- Reporter: timmyjose | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.2 Keywords: parsec, | Operating System: MacOS X ghc8.0.2, macOS Sierra | Architecture: x86_64 | Type of failure: Compile-time (amd64) | crash or panic Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- I am working through "Create your own Scheme in 48 hours", and the following program: $ cat SimpleParser.hs import Text.ParserCombinators.Parsec hiding (spaces) symbol :: Parser Char symbol = anyOf "!$%&|*+-/:<=?>@^_^~#" causes GHC to crash and burn with a panic message. Please find the details as follows: ** PLATFORM and OS DETAILS ** $ sw_vers ProductName: Mac OS X ProductVersion: 10.12.2 BuildVersion: 16C67 $ uname -a Darwin 16.3.0 Darwin Kernel Version 16.3.0: Thu Nov 17 20:23:58 PST 2016; root:xnu-3789.31.2~1/RELEASE_X86_64 x86_64 ** GHC and Parsec version** $ ghc --version The Glorious Glasgow Haskell Compilation System, version 8.0.2 $ ghc-pkg list | grep -i parsec attoparsec-0.13.1.0 parsec-3.1.11 ** crash error message ** $ ghc -v3 SimpleParser.hs Glasgow Haskell Compiler, Version 8.0.2, stage 2 booted by GHC version 7.10.3 Using binary package database: /Library/Frameworks/GHC.framework/Versions/8.0.2-x86_64/usr/lib/ghc-8.0.2/package.conf.d/package.cache Using binary package database: /Users//.ghc/x86_64-darwin-8.0.2/package.conf.d/package.cache loading package database /Library/Frameworks/GHC.framework/Versions/8.0.2-x86_64/usr/lib/ghc-8.0.2/package.conf.d loading package database /Users//.ghc/x86_64-darwin-8.0.2/package.conf.d wired-in package ghc-prim mapped to ghc-prim-0.5.0.0 wired-in package integer-gmp mapped to integer-gmp-1.0.0.1 wired-in package base mapped to base-4.9.1.0 wired-in package rts mapped to rts wired-in package template-haskell mapped to template-haskell-2.11.1.0 wired-in package ghc mapped to ghc-8.0.2 wired-in package dph-seq not found. wired-in package dph-par not found. Hsc static flags: loading package database /Library/Frameworks/GHC.framework/Versions/8.0.2-x86_64/usr/lib/ghc-8.0.2/package.conf.d loading package database /Users/z0ltan/.ghc/x86_64-darwin-8.0.2/package.conf.d wired-in package ghc-prim mapped to ghc-prim-0.5.0.0 wired-in package integer-gmp mapped to integer-gmp-1.0.0.1 wired-in package base mapped to base-4.9.1.0 wired-in package rts mapped to rts-1.0 wired-in package template-haskell mapped to template-haskell-2.11.1.0 wired-in package ghc mapped to ghc-8.0.2 wired-in package dph-seq not found. wired-in package dph-par not found. *** Chasing dependencies: Chasing modules from: *SimpleParser.hs !!! Chasing dependencies: finished in 0.62 milliseconds, allocated 0.337 megabytes Stable obj: [] Stable BCO: [] Ready for upsweep [NONREC ModSummary { ms_hs_date = 2017-06-28 09:58:23 UTC ms_mod = Main, ms_textual_imps = [(Nothing, Prelude), (Nothing, Text.ParserCombinators.Parsec)] ms_srcimps = [] }] *** Deleting temp files: Deleting: compile: input file SimpleParser.hs *** Checking old interface for Main: [1 of 1] Compiling Main ( SimpleParser.hs, SimpleParser.o ) *** Parser [Main]: !!! Parser [Main]: finished in 0.20 milliseconds, allocated 0.134 megabytes *** Renamer/typechecker [Main]: *** Deleting temp files: Deleting: *** Deleting temp dirs: Deleting: ghc: panic! (the 'impossible' happened) (GHC version 8.0.2 for x86_64-apple-darwin): initTc: unsolved constraints WC {wc_insol = [W] anyOf_a1lw :: t_a1lv[tau:1] (CHoleCan: anyOf)} Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jun 28 10:35:18 2017 From: ghc-devs at haskell.org (GHC) Date: Wed, 28 Jun 2017 10:35:18 -0000 Subject: [GHC] #13889: GHC 8.0.2 panics when trying a simple snippet involving Parsec Message-ID: <048.687561c0b2094c184d470f52797d1735@haskell.org> #13889: GHC 8.0.2 panics when trying a simple snippet involving Parsec -------------------------------------+------------------------------------- Reporter: timmyjose | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.2 Keywords: parsec, | Operating System: MacOS X ghc8.0.2, macOS Sierra | Architecture: x86_64 | Type of failure: Compile-time (amd64) | crash or panic Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- I am working through "Create your own Scheme in 48 hours", and the following program: {{{ $ cat SimpleParser.hs import Text.ParserCombinators.Parsec hiding (spaces) symbol :: Parser Char symbol = anyOf "!$%&|*+-/:<=?>@^_^~#" }}} causes GHC to crash and burn with a panic message. Please find the details as follows: ** PLATFORM and OS DETAILS ** {{{ $ sw_vers ProductName: Mac OS X ProductVersion: 10.12.2 BuildVersion: 16C67 $ uname -a Darwin 16.3.0 Darwin Kernel Version 16.3.0: Thu Nov 17 20:23:58 PST 2016; root:xnu-3789.31.2~1/RELEASE_X86_64 x86_64 }}} ** GHC and Parsec version** {{{ $ ghc --version The Glorious Glasgow Haskell Compilation System, version 8.0.2 $ ghc-pkg list | grep -i parsec attoparsec-0.13.1.0 parsec-3.1.11 }}} ** crash error message ** {{{ $ ghc -v3 SimpleParser.hs Glasgow Haskell Compiler, Version 8.0.2, stage 2 booted by GHC version 7.10.3 Using binary package database: /Library/Frameworks/GHC.framework/Versions/8.0.2-x86_64/usr/lib/ghc-8.0.2/package.conf.d/package.cache Using binary package database: /Users//.ghc/x86_64-darwin-8.0.2/package.conf.d/package.cache loading package database /Library/Frameworks/GHC.framework/Versions/8.0.2-x86_64/usr/lib/ghc-8.0.2/package.conf.d loading package database /Users//.ghc/x86_64-darwin-8.0.2/package.conf.d wired-in package ghc-prim mapped to ghc-prim-0.5.0.0 wired-in package integer-gmp mapped to integer-gmp-1.0.0.1 wired-in package base mapped to base-4.9.1.0 wired-in package rts mapped to rts wired-in package template-haskell mapped to template-haskell-2.11.1.0 wired-in package ghc mapped to ghc-8.0.2 wired-in package dph-seq not found. wired-in package dph-par not found. Hsc static flags: loading package database /Library/Frameworks/GHC.framework/Versions/8.0.2-x86_64/usr/lib/ghc-8.0.2/package.conf.d loading package database /Users/z0ltan/.ghc/x86_64-darwin-8.0.2/package.conf.d wired-in package ghc-prim mapped to ghc-prim-0.5.0.0 wired-in package integer-gmp mapped to integer-gmp-1.0.0.1 wired-in package base mapped to base-4.9.1.0 wired-in package rts mapped to rts-1.0 wired-in package template-haskell mapped to template-haskell-2.11.1.0 wired-in package ghc mapped to ghc-8.0.2 wired-in package dph-seq not found. wired-in package dph-par not found. *** Chasing dependencies: Chasing modules from: *SimpleParser.hs !!! Chasing dependencies: finished in 0.62 milliseconds, allocated 0.337 megabytes Stable obj: [] Stable BCO: [] Ready for upsweep [NONREC ModSummary { ms_hs_date = 2017-06-28 09:58:23 UTC ms_mod = Main, ms_textual_imps = [(Nothing, Prelude), (Nothing, Text.ParserCombinators.Parsec)] ms_srcimps = [] }] *** Deleting temp files: Deleting: compile: input file SimpleParser.hs *** Checking old interface for Main: [1 of 1] Compiling Main ( SimpleParser.hs, SimpleParser.o ) *** Parser [Main]: !!! Parser [Main]: finished in 0.20 milliseconds, allocated 0.134 megabytes *** Renamer/typechecker [Main]: *** Deleting temp files: Deleting: *** Deleting temp dirs: Deleting: ghc: panic! (the 'impossible' happened) (GHC version 8.0.2 for x86_64-apple-darwin): initTc: unsolved constraints WC {wc_insol = [W] anyOf_a1lw :: t_a1lv[tau:1] (CHoleCan: anyOf)} Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jun 28 10:37:40 2017 From: ghc-devs at haskell.org (GHC) Date: Wed, 28 Jun 2017 10:37:40 -0000 Subject: [GHC] #13888: GHC 8.0.2 panics when trying a simple snippet involving Parsec In-Reply-To: <048.209ad257f958bd88adecc8c8a6266ee6@haskell.org> References: <048.209ad257f958bd88adecc8c8a6266ee6@haskell.org> Message-ID: <063.0a4cf83354966d355e2aeba99da3c5b1@haskell.org> #13888: GHC 8.0.2 panics when trying a simple snippet involving Parsec -------------------------------------+------------------------------------- Reporter: timmyjose | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 8.0.2 Resolution: duplicate | Keywords: parsec, | ghc8.0.2, macOS Sierra Operating System: MacOS X | Architecture: x86_64 Type of failure: Compile-time | (amd64) crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by timmyjose): * status: new => closed * resolution: => duplicate -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jun 28 11:24:33 2017 From: ghc-devs at haskell.org (GHC) Date: Wed, 28 Jun 2017 11:24:33 -0000 Subject: [GHC] #12087: Inconsistency in GADTs? In-Reply-To: <051.271b252c8ff7e6b4a86908e0694bb2a9@haskell.org> References: <051.271b252c8ff7e6b4a86908e0694bb2a9@haskell.org> Message-ID: <066.10a3473919ef71b2ff0e4cbd15008018@haskell.org> #12087: Inconsistency in GADTs? -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: RyanGlScott Type: task | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: GADTs Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #11540 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): I agree this is possible in principle but it is fiddly in practice. What about {{{ MkF :: Ord a => a -> Eq a => F a }}} which ought to work too. > This isn't exactly what the user wrote, but it's equivalent and serviceable. Yes but we'll soon have people asking that `:t MkF` prints out the type they wrote. Nothing deep here I think, but I'm not persuaded that it's a high priority. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jun 28 11:44:24 2017 From: ghc-devs at haskell.org (GHC) Date: Wed, 28 Jun 2017 11:44:24 -0000 Subject: [GHC] #13885: Template Haskell doesn't freshen GADT type variables properly In-Reply-To: <050.316bfca35535b28b80cdb6a4e733201d@haskell.org> References: <050.316bfca35535b28b80cdb6a4e733201d@haskell.org> Message-ID: <065.974b78e20dff1cb4f3e78e668328b4c6@haskell.org> #13885: Template Haskell doesn't freshen GADT type variables properly -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): OK fine -- if someone wants to make this so it'd be fine by me. But please comment the code so we know it's for convenience for clients rather than correctness. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jun 28 12:49:19 2017 From: ghc-devs at haskell.org (GHC) Date: Wed, 28 Jun 2017 12:49:19 -0000 Subject: [GHC] #9588: Add `MonadPlus (Either e)` and `Alternative (Either e)` instances In-Reply-To: <042.81b9305fea59cb0eb6b8168a5d80498d@haskell.org> References: <042.81b9305fea59cb0eb6b8168a5d80498d@haskell.org> Message-ID: <057.e9c82ae2b5c77235f68f373834869654@haskell.org> #9588: Add `MonadPlus (Either e)` and `Alternative (Either e)` instances -------------------------------------+------------------------------------- Reporter: hvr | Owner: hvr Type: task | Status: new Priority: normal | Milestone: ⊥ Component: Core Libraries | Version: Resolution: | Keywords: report-impact Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #10755 #12160 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Iceland_jack): intended? {{{#!hs $ ghci-8.0.1 GHCi, version 8.0.1: http://www.haskell.org/ghc/ :? for help Loaded GHCi configuration from /apps/strats/.ghci > import Data.Foldable > import Control.Applicative > import Control.Monad.Trans.Error :1:1: warning: [-Wdeprecations] Module ‘Control.Monad.Trans.Error’ is deprecated: Use Control.Monad.Trans.Except instead > Left "A" <|> Left "B" Left "B" > asum [Left "A", Left "B"] Left "" }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jun 28 13:09:35 2017 From: ghc-devs at haskell.org (GHC) Date: Wed, 28 Jun 2017 13:09:35 -0000 Subject: [GHC] #13879: Strange interaction between higher-rank kinds and type synonyms In-Reply-To: <050.03cb88421049abbd653e9048089d3969@haskell.org> References: <050.03cb88421049abbd653e9048089d3969@haskell.org> Message-ID: <065.5116f2564ce8c1b01a28206b2c2ed909@haskell.org> #13879: Strange interaction between higher-rank kinds and type synonyms -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.1 checker) | Resolution: | Keywords: TypeInType Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Simon Peyton Jones ): In [changeset:"4bdac331207e10650da9d3bf1b446bc8be3c069a/ghc" 4bdac331/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="4bdac331207e10650da9d3bf1b446bc8be3c069a" Fix the in-scope set in TcHsType.instantiateTyN See Trac #13879 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jun 28 13:09:35 2017 From: ghc-devs at haskell.org (GHC) Date: Wed, 28 Jun 2017 13:09:35 -0000 Subject: [GHC] #13879: Strange interaction between higher-rank kinds and type synonyms In-Reply-To: <050.03cb88421049abbd653e9048089d3969@haskell.org> References: <050.03cb88421049abbd653e9048089d3969@haskell.org> Message-ID: <065.68cf31ad57706afc6e9a7ee5888a6ce1@haskell.org> #13879: Strange interaction between higher-rank kinds and type synonyms -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.1 checker) | Resolution: | Keywords: TypeInType Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Simon Peyton Jones ): In [changeset:"fae672f647fe00c303d8fb56971563c1a76ad04e/ghc" fae672f/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="fae672f647fe00c303d8fb56971563c1a76ad04e" Fix constraint solving for forall-types Trac #13879 showed that when we were trying to solve (forall z1 (y1::z1). ty1) ~ (forall z2 (y2:z2). ty2) we'd end up spitting out z1~z2 with no binding site for them. Those kind equalities need to be inside the implication. I ended up re-factoring the code for solving forall-equalities. It's quite nice now. }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jun 28 13:09:35 2017 From: ghc-devs at haskell.org (GHC) Date: Wed, 28 Jun 2017 13:09:35 -0000 Subject: [GHC] #13879: Strange interaction between higher-rank kinds and type synonyms In-Reply-To: <050.03cb88421049abbd653e9048089d3969@haskell.org> References: <050.03cb88421049abbd653e9048089d3969@haskell.org> Message-ID: <065.043807140c0c94fbfe98c5c79c058252@haskell.org> #13879: Strange interaction between higher-rank kinds and type synonyms -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.1 checker) | Resolution: | Keywords: TypeInType Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Simon Peyton Jones ): In [changeset:"c80920d26f4eef8e87c130412d007628cff7589d/ghc" c80920d2/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="c80920d26f4eef8e87c130412d007628cff7589d" Do zonking in tcLHsKindSig Trac #13879 showed that there was a missing zonk in tcLHsKind. I also renamed it to tcLHsKindSig, for consistency with type signatures There's a commment to explain why the zonk is needed. }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jun 28 13:18:03 2017 From: ghc-devs at haskell.org (GHC) Date: Wed, 28 Jun 2017 13:18:03 -0000 Subject: [GHC] #13890: Loss of inlining after strictness analysis Message-ID: <046.e7864ade8446632cd5f904a1bec0b5d4@haskell.org> #13890: Loss of inlining after strictness analysis -------------------------------------+------------------------------------- Reporter: simonpj | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- While investigating something else I saw this in the final `Tidy Core` after optimisation {{{ join { wild_X5jU [Dmd=] :: (# State# RealWorld, Array Int HValue #) [LclId[JoinId(0)], Unf=Unf{Src=InlineStable, TopLvl=False, Value=False, ConLike=False, WorkFree=False, Expandable=False, Guidance=ALWAYS_IF(arity=0,unsat_ok=True,boring_ok=False) Tmpl= jump $j1_s5RP w_s5Qs}] wild_X5jU = jump $j1_s5RP ww_s5Qw } in jump wild_X5jU; }}} That's ridiculous! Why wasn't it inlined at its (only!) use site? It turns out that * The original `InlineStable` came from when `wild` was lambda-bound. See `Note [Case binders and join points]` in `Simplify.hs` * But then worker-wrapper let-binds that previously-lambda-boudn arg in `WwLib.mkWWstr_one`. But it does not remove the unfolding. That's bad; in contrast, when we beta-reduce we are careful to remove the unfolding; see `Note [Zap unfolding when beta-reducing]` in `Simplify.hs`. * We don't `preInlineUnconditionally` things with stable unfoldings; see `Note [Stable unfoldings and preInlineUnconditionally]` in `SimplUtils` Net result: it doesn't get inlined at all! Easy fix: zap the unfolding in `mkWWstr_one` as well. I'm unhappy with the whole business of passing both boxed and unboxed versions, described in `Note [Case binders and join points]`. It smells wrong, and this ticket is another canary. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jun 28 13:21:00 2017 From: ghc-devs at haskell.org (GHC) Date: Wed, 28 Jun 2017 13:21:00 -0000 Subject: [GHC] #13879: Strange interaction between higher-rank kinds and type synonyms In-Reply-To: <050.03cb88421049abbd653e9048089d3969@haskell.org> References: <050.03cb88421049abbd653e9048089d3969@haskell.org> Message-ID: <065.e46013c1cf965a86a42440ef6c667cda@haskell.org> #13879: Strange interaction between higher-rank kinds and type synonyms -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: merge Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.1 checker) | Resolution: | Keywords: TypeInType Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: GHC rejects | Test Case: valid program | typecheck/should_compile/T13879 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * testcase: => typecheck/should_compile/T13879 * status: new => merge Comment: All done! Probably worth merging these patches; I'm pretty sure they won't trigger new bugs. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jun 28 13:27:03 2017 From: ghc-devs at haskell.org (GHC) Date: Wed, 28 Jun 2017 13:27:03 -0000 Subject: [GHC] #13886: GHC panic when using GHC plugins In-Reply-To: <048.4e65bf02b6c4ff69cd509bbe731fe7ea@haskell.org> References: <048.4e65bf02b6c4ff69cd509bbe731fe7ea@haskell.org> Message-ID: <063.3a04d9434b8fffeed3d39704588b1b5e@haskell.org> #13886: GHC panic when using GHC plugins -------------------------------------+------------------------------------- Reporter: Darwin226 | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.2 Resolution: | Keywords: Operating System: Windows | Architecture: x86_64 Type of failure: Compile-time | (amd64) crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Darwin226): How did you get deepseq to compile? It gets stuck on some module saying it needs TypeSynonymInstances enabled. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jun 28 13:29:32 2017 From: ghc-devs at haskell.org (GHC) Date: Wed, 28 Jun 2017 13:29:32 -0000 Subject: [GHC] #13891: forkIO can trivially defeat bracket Message-ID: <046.bb2170e97e55c0c11118313e8136933d@haskell.org> #13891: forkIO can trivially defeat bracket -------------------------------------+------------------------------------- Reporter: bgamari | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- Consider this program, {{{#!hs import Control.Concurrent import Control.Exception main = do putStrLn "forking" forkIO $ bracket (putStrLn "forked") (const $ putStrLn "finalize") (const $ putStrLn "hello" >> threadDelay 100000000) threadDelay 10000 putStrLn "done" }}} Would you predict that it would print `finalize`? Answer: no. It will print, {{{ forking forked hello done }}} It would pointed out by an author of a cryptographic library (`raaz`) that this is quite bad as it means that secure memory could leak out uncleared. It's not entirely clear how best to deal with this. Perhaps raise a `ThreadKilled` async exception to all running threads during RTS shutdown, followed by a synchronization? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jun 28 13:47:31 2017 From: ghc-devs at haskell.org (GHC) Date: Wed, 28 Jun 2017 13:47:31 -0000 Subject: [GHC] #13890: Loss of inlining after strictness analysis In-Reply-To: <046.e7864ade8446632cd5f904a1bec0b5d4@haskell.org> References: <046.e7864ade8446632cd5f904a1bec0b5d4@haskell.org> Message-ID: <061.aa2ac50d1e3d559aaecd49ae6f61a925@haskell.org> #13890: Loss of inlining after strictness analysis -------------------------------------+------------------------------------- Reporter: simonpj | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Simon Peyton Jones ): In [changeset:"87c5fdbba118db1938d699951a811cc2f6206d4d/ghc" 87c5fdb/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="87c5fdbba118db1938d699951a811cc2f6206d4d" Zap stable unfoldings in worker/wrapper This patch fixes the buglet described in Trac #13890. }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jun 28 13:48:02 2017 From: ghc-devs at haskell.org (GHC) Date: Wed, 28 Jun 2017 13:48:02 -0000 Subject: [GHC] #13890: Loss of inlining after strictness analysis In-Reply-To: <046.e7864ade8446632cd5f904a1bec0b5d4@haskell.org> References: <046.e7864ade8446632cd5f904a1bec0b5d4@haskell.org> Message-ID: <061.b92df4cc28fd8b56fed33fb234d37fcb@haskell.org> #13890: Loss of inlining after strictness analysis -------------------------------------+------------------------------------- Reporter: simonpj | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * status: new => closed * resolution: => fixed -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jun 28 14:37:21 2017 From: ghc-devs at haskell.org (GHC) Date: Wed, 28 Jun 2017 14:37:21 -0000 Subject: [GHC] #13890: Loss of inlining after strictness analysis In-Reply-To: <046.e7864ade8446632cd5f904a1bec0b5d4@haskell.org> References: <046.e7864ade8446632cd5f904a1bec0b5d4@haskell.org> Message-ID: <061.ce3c709d5e35060ddc69048027ec8436@haskell.org> #13890: Loss of inlining after strictness analysis -------------------------------------+------------------------------------- Reporter: simonpj | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: fixed | Keywords: Inlining Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by mpickering): * keywords: => Inlining -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jun 28 14:43:11 2017 From: ghc-devs at haskell.org (GHC) Date: Wed, 28 Jun 2017 14:43:11 -0000 Subject: [GHC] #13886: GHC panic when using GHC plugins In-Reply-To: <048.4e65bf02b6c4ff69cd509bbe731fe7ea@haskell.org> References: <048.4e65bf02b6c4ff69cd509bbe731fe7ea@haskell.org> Message-ID: <063.ca7886af194d56080ad1a78265d70a4d@haskell.org> #13886: GHC panic when using GHC plugins -------------------------------------+------------------------------------- Reporter: Darwin226 | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.2 Resolution: | Keywords: Operating System: Windows | Architecture: x86_64 Type of failure: Compile-time | (amd64) crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): Are you using `stack`? If so, try using the directions here: http://taylor.fausak.me/2017/05/17/testing-ghc-release-candidates-with- stack/ (Due to a quirk in the way `stack` operates, you'll have to use a particular `deepseq` version in `extra-deps`.) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jun 28 14:45:58 2017 From: ghc-devs at haskell.org (GHC) Date: Wed, 28 Jun 2017 14:45:58 -0000 Subject: [GHC] #13886: GHC panic when using GHC plugins In-Reply-To: <048.4e65bf02b6c4ff69cd509bbe731fe7ea@haskell.org> References: <048.4e65bf02b6c4ff69cd509bbe731fe7ea@haskell.org> Message-ID: <063.98c82e06bac000386569a9be2bbf8851@haskell.org> #13886: GHC panic when using GHC plugins -------------------------------------+------------------------------------- Reporter: Darwin226 | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.2 Resolution: | Keywords: Operating System: Windows | Architecture: x86_64 Type of failure: Compile-time | (amd64) crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by mpickering): I have version `1.4.3.0` which I assume I installed from the github repo as it doesn't appear on hackage. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jun 28 14:58:26 2017 From: ghc-devs at haskell.org (GHC) Date: Wed, 28 Jun 2017 14:58:26 -0000 Subject: [GHC] #13875: ApplicativeDo desugaring is lazier than standard desugaring In-Reply-To: <045.2eda858359df0999208d04da5f95a1da@haskell.org> References: <045.2eda858359df0999208d04da5f95a1da@haskell.org> Message-ID: <060.91a7ce24307f77be0057fe453d2c6d60@haskell.org> #13875: ApplicativeDo desugaring is lazier than standard desugaring -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: simonmar Type: bug | Status: new Priority: high | Milestone: 8.2.1 Component: Compiler | Version: 8.3 Resolution: | Keywords: ApplicativeDo Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Other | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonmar): This bug makes #13242 moot, incidentally. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jun 28 15:02:12 2017 From: ghc-devs at haskell.org (GHC) Date: Wed, 28 Jun 2017 15:02:12 -0000 Subject: [GHC] #13892: Add some benchmarks to nofib from Andras Kovac's Eff benchmarks Message-ID: <049.64e07177e9110058c04a019d46370d44@haskell.org> #13892: Add some benchmarks to nofib from Andras Kovac's Eff benchmarks -------------------------------------+------------------------------------- Reporter: mpickering | Owner: (none) Type: task | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- Andras has a bunch of different benchmarks for different effect handler code which stresses the optimiser in interesting ways. It would be good to add some of these benchmarks to nofib as they are likely quite different from a lot of the examples already in there. https://github.com/AndrasKovacs/misc-stuff/tree/master/haskell/Eff -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jun 28 15:02:26 2017 From: ghc-devs at haskell.org (GHC) Date: Wed, 28 Jun 2017 15:02:26 -0000 Subject: [GHC] #13892: Add some benchmarks to nofib from Andras Kovac's Eff benchmarks In-Reply-To: <049.64e07177e9110058c04a019d46370d44@haskell.org> References: <049.64e07177e9110058c04a019d46370d44@haskell.org> Message-ID: <064.bd78cb38cfd6bc23a94ce97714bf01e0@haskell.org> #13892: Add some benchmarks to nofib from Andras Kovac's Eff benchmarks -------------------------------------+------------------------------------- Reporter: mpickering | Owner: mpickering Type: task | Status: new Priority: normal | Milestone: Component: NoFib benchmark | Version: 8.0.1 suite | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by mpickering): * owner: (none) => mpickering * component: Compiler => NoFib benchmark suite -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jun 28 15:27:17 2017 From: ghc-devs at haskell.org (GHC) Date: Wed, 28 Jun 2017 15:27:17 -0000 Subject: [GHC] #13879: Strange interaction between higher-rank kinds and type synonyms In-Reply-To: <050.03cb88421049abbd653e9048089d3969@haskell.org> References: <050.03cb88421049abbd653e9048089d3969@haskell.org> Message-ID: <065.2dc14cd298e39af83ae806cd7ee28943@haskell.org> #13879: Strange interaction between higher-rank kinds and type synonyms -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: merge Priority: normal | Milestone: 8.2.1 Component: Compiler (Type | Version: 8.0.1 checker) | Resolution: | Keywords: TypeInType Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: GHC rejects | Test Case: valid program | typecheck/should_compile/T13879 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * milestone: => 8.2.1 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jun 28 15:41:13 2017 From: ghc-devs at haskell.org (GHC) Date: Wed, 28 Jun 2017 15:41:13 -0000 Subject: [GHC] #13892: Add some benchmarks to nofib from Andras Kovac's Eff benchmarks In-Reply-To: <049.64e07177e9110058c04a019d46370d44@haskell.org> References: <049.64e07177e9110058c04a019d46370d44@haskell.org> Message-ID: <064.efb3da60242c8adcceb43d4f53c93ea7@haskell.org> #13892: Add some benchmarks to nofib from Andras Kovac's Eff benchmarks -------------------------------------+------------------------------------- Reporter: mpickering | Owner: mpickering Type: task | Status: new Priority: normal | Milestone: Component: NoFib benchmark | Version: 8.0.1 suite | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): Oooohh yes please! -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jun 28 15:48:24 2017 From: ghc-devs at haskell.org (GHC) Date: Wed, 28 Jun 2017 15:48:24 -0000 Subject: [GHC] #12087: Inconsistency in GADTs? In-Reply-To: <051.271b252c8ff7e6b4a86908e0694bb2a9@haskell.org> References: <051.271b252c8ff7e6b4a86908e0694bb2a9@haskell.org> Message-ID: <066.d36306ac43b61f251d6f1a3f5f1a08ca@haskell.org> #12087: Inconsistency in GADTs? -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: RyanGlScott Type: task | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: GADTs Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #11540 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): Replying to [comment:4 simonpj]: > I agree this is possible in principle but it is fiddly in practice. What about > {{{ > MkF :: Ord a => a -> Eq a => F a > }}} > which ought to work too. Sure, I completely agree. `tcSplitNestedSigmaTys` can handle that case, so `tcSplitNestedLHsSigmaTys` ought to as well. > > This isn't exactly what the user wrote, but it's equivalent and serviceable. > > Yes but we'll soon have people asking that `:t MkF` prints out the type they wrote. We can cross that bridge when we come to it. FWIW, GHC doesn't have a solid track record of preserving nested sigma types for functions either: {{{ λ> let f :: Ord a => Eq a => a -> Bool; f = undefined λ> :type f f :: Ord a => a -> Bool λ> let g :: Ord a => a -> Eq a => a; g = undefined λ> :type g g :: Ord a1 => a2 -> a1 }}} So it (personally) wouldn't bother me to have `:type MkF` print out something slightly different than what I typed. After all, if I'm using nested sigma types in the first place, there's a good chance I know why GHC's displayed type is tweaked (but equivalent). -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jun 28 15:53:25 2017 From: ghc-devs at haskell.org (GHC) Date: Wed, 28 Jun 2017 15:53:25 -0000 Subject: [GHC] #13875: ApplicativeDo desugaring is lazier than standard desugaring In-Reply-To: <045.2eda858359df0999208d04da5f95a1da@haskell.org> References: <045.2eda858359df0999208d04da5f95a1da@haskell.org> Message-ID: <060.1802813453ce5d3efb14f6c0ebf935c1@haskell.org> #13875: ApplicativeDo desugaring is lazier than standard desugaring -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: simonmar Type: bug | Status: new Priority: high | Milestone: 8.2.1 Component: Compiler | Version: 8.3 Resolution: | Keywords: ApplicativeDo Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Other | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3681 Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonmar): * differential: => Phab:D3681 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jun 28 16:04:30 2017 From: ghc-devs at haskell.org (GHC) Date: Wed, 28 Jun 2017 16:04:30 -0000 Subject: [GHC] #13848: Unexpected order of variable quantification with GADT constructor In-Reply-To: <050.1bdc037c5d3daf9f53281904769def22@haskell.org> References: <050.1bdc037c5d3daf9f53281904769def22@haskell.org> Message-ID: <065.fdb0e31fc7bbc1fc93b867d8d4153e3f@haskell.org> #13848: Unexpected order of variable quantification with GADT constructor -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.1 checker) | Keywords: Resolution: | TypeApplications Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): OK, I think I'm starting to see the picture more clearly. However, some of the details are still hazy to me. In particular, `tcConDecl` is far from the only place that uses `buildDataCon` to construct a `DataCon`. However, as far as I can tell, `tcConDecl` is the //only// place that knows exactly what order the user wrote the constructor's type variables in. This is important because we might write a GADT to an interface file and read it back in [http://git.haskell.org/ghc.git/blob/78c80c250021ccb7a84afaabebe0d69f9b9372ee:/compiler/iface/MkIface.hs#l1544 tyConToIfaceDecl], which also uses `buildDataCon`. However, we've lost the order of the type variables used in the wrapper type by that point, since `IfaceData` doesn't store the wrapper type! This suggests to me that we need to beef up `IfaceData` to accommodate this change. Should we be storing the wrapper type as a field of `IfaceData` as well? Or am I barking up the wrong tree? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jun 28 16:11:58 2017 From: ghc-devs at haskell.org (GHC) Date: Wed, 28 Jun 2017 16:11:58 -0000 Subject: [GHC] #13893: Improved Help for Control.Concurrent and Control.Exception when "variable not in scope" Message-ID: <044.50a1c8e97ad1d72587a33a02855fe4cb@haskell.org> #13893: Improved Help for Control.Concurrent and Control.Exception when "variable not in scope" -------------------------------------+------------------------------------- Reporter: vanto | Owner: (none) Type: feature | Status: new request | Priority: normal | Milestone: Component: Compiler | Version: 8.0.2 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: Poor/confusing Unknown/Multiple | error message Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- The piece of code that bgamari wrote in {{{#13891}}} is interesting from the point of view of the error messages.\\ {{{ main = do putStrLn "forking" forkIO $ bracket (putStrLn "forked") (const $ putStrLn "finalize") (const $ putStrLn "hello" >> threadDelay 100000000) threadDelay 10000 putStrLn "done" }}} When the imports are not written GHC answers.\\ {{{ Prelude> :l testfork [1 of 1] Compiling Main ( testfork.hs, interpreted ) testfork.hs:6:5: error: Variable not in scope: forkIO :: t0 -> IO a0 testfork.hs:6:14: error: Variable not in scope: bracket :: IO () -> (b1 -> IO ()) -> (b0 -> IO b2) -> t0 testfork.hs:6:101: error: Variable not in scope: threadDelay :: Integer -> IO b2 testfork.hs:7:5: error: Variable not in scope: threadDelay :: Integer -> IO a1 Failed, modules loaded: none. Prelude> }}} It would be advisable to complete by:\\ {{{Perhaps you intended to import Control.Concurrent}}} for {{{forkIO}}} and {{{threadDelay}}}.\\ {{{Perhaps you intended to import Control.Exception}}} for {{{bracket}}}.\\ I hope you have a way to write it once for all the variables involved. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jun 28 19:30:05 2017 From: ghc-devs at haskell.org (GHC) Date: Wed, 28 Jun 2017 19:30:05 -0000 Subject: [GHC] #13886: GHC panic when using GHC plugins In-Reply-To: <048.4e65bf02b6c4ff69cd509bbe731fe7ea@haskell.org> References: <048.4e65bf02b6c4ff69cd509bbe731fe7ea@haskell.org> Message-ID: <063.8ce8ea9b381e42391ea07f67f6f4d123@haskell.org> #13886: GHC panic when using GHC plugins -------------------------------------+------------------------------------- Reporter: Darwin226 | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.2 Resolution: | Keywords: Operating System: Windows | Architecture: x86_64 Type of failure: Compile-time | (amd64) crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Darwin226): I'm slowly getting through the build. Currently getting stuck on hashable but the error doesn't seem to be fixed even in HEAD of the repo. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jun 28 19:53:42 2017 From: ghc-devs at haskell.org (GHC) Date: Wed, 28 Jun 2017 19:53:42 -0000 Subject: [GHC] #13886: GHC panic when using GHC plugins In-Reply-To: <048.4e65bf02b6c4ff69cd509bbe731fe7ea@haskell.org> References: <048.4e65bf02b6c4ff69cd509bbe731fe7ea@haskell.org> Message-ID: <063.d0a32496f1529d4cfe183bd11a85d542@haskell.org> #13886: GHC panic when using GHC plugins -------------------------------------+------------------------------------- Reporter: Darwin226 | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.2 Resolution: | Keywords: Operating System: Windows | Architecture: x86_64 Type of failure: Compile-time | (amd64) crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): Also make sure to use `hashable-1.2.6.0` instead of `hashable-1.2.6.1`, as the latter only works with an as-of-yet unreleased 8.2.1 release candidate. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jun 28 20:36:43 2017 From: ghc-devs at haskell.org (GHC) Date: Wed, 28 Jun 2017 20:36:43 -0000 Subject: [GHC] #8281: The impossible happened: primRepToFFIType In-Reply-To: <044.47e20917996e473150de04c1ce1afc0b@haskell.org> References: <044.47e20917996e473150de04c1ce1afc0b@haskell.org> Message-ID: <059.9b87441f02fed6f8c2da796ad36a971b@haskell.org> #8281: The impossible happened: primRepToFFIType -------------------------------------+------------------------------------- Reporter: tibbe | Owner: (none) Type: bug | Status: patch Priority: high | Milestone: 8.4.1 Component: Compiler | Version: 7.6.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3619 Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): How does Phab:D3682 look? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jun 28 21:07:03 2017 From: ghc-devs at haskell.org (GHC) Date: Wed, 28 Jun 2017 21:07:03 -0000 Subject: [GHC] #13881: Inexplicable error message when using out-of-scope type variable in pattern type signature In-Reply-To: <050.64fe59f3330624a2ee7d23968276dcc1@haskell.org> References: <050.64fe59f3330624a2ee7d23968276dcc1@haskell.org> Message-ID: <065.120d072fb8d32fdc901e22dc52ab13b1@haskell.org> #13881: Inexplicable error message when using out-of-scope type variable in pattern type signature -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.1 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Poor/confusing | Unknown/Multiple error message | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): I attempted to debug this a bit. I at least know why the error message is happening. In an attempt to detect type variables that are manufactured out of thin air in pattern signatures, such as this: {{{#!hs type T a = Int f :: Int -> Int f (x :: T a) = ... }}} GHC first collects the tyvars of the pattern signature, then collects the //exact// tyvars (read: after type synonym expansion) of the typechecked pattern signature, and if any tyvars from the first set aren't in the second set, it errors. Seems simple enough. Here's what I don't get though. Surprisingly, this variant of the program compiles, even with `ScopedTypeVariables`: {{{#!hs fl :: forall (l :: [a]). Sing l -> Sing l fl (SNil :: Sing (song :: [a])) = (SNil :: Sing l) :: Sing song fl (SCons x xs) = SCons x xs }}} Here, the pattern signature for `SNil` //binds// the tyvar `song`, and type inference figures out that it's equal to `l`. As a result, everything works out. But in the original variant of the program: {{{#!hs fl :: forall (l :: [a]). Sing l -> Sing l fl (SNil :: Sing (l :: [y])) = SNil fl (SCons x xs) = SCons x xs }}} Due to `ScopedTypeVariables`, the pattern signature is not binding `l`. Therefore, after typechecking the pattern signature `l :: [y]` becomes `l :: [a]`, since `a` is the kind variable we used when quantifying `l` in the type signature for `fl`. But this presents a problem, because: 1. The kind vars of the original pattern signature include `y` 2. The exact kind vars of the typechecked pattern signature do //not// include `y` (only `a`) Thus, GHC errors. I'm still not sure of the best way to inform GHC that `y` isn't bound by a type synonym, however... -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jun 28 21:51:14 2017 From: ghc-devs at haskell.org (GHC) Date: Wed, 28 Jun 2017 21:51:14 -0000 Subject: [GHC] #13886: GHC panic when using GHC plugins In-Reply-To: <048.4e65bf02b6c4ff69cd509bbe731fe7ea@haskell.org> References: <048.4e65bf02b6c4ff69cd509bbe731fe7ea@haskell.org> Message-ID: <063.475427e9db8dce50d07cc8285d28b4be@haskell.org> #13886: GHC panic when using GHC plugins -------------------------------------+------------------------------------- Reporter: Darwin226 | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.2 Resolution: | Keywords: Operating System: Windows | Architecture: x86_64 Type of failure: Compile-time | (amd64) crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Darwin226): Ok, that did it for hashable, now after adding a few more manual versions I'm stuck at {{{ Warning: This package indirectly depends on multiple versions of the same package. This is very likely to cause a compile failure. package time (time-1.8.0.1) requires Win32-2.5.4.1 package process (process-1.6.0.0) requires Win32-2.5.4.1 package ghc (ghc-8.2.0.20170507) requires Win32-2.5.4.1 package directory (directory-1.3.0.2) requires Win32-2.5.4.1 package time (time-1.8.0.1-7Vbd89jgVoWBI75ow03wJC) requires Win32-2.5.4.1-8epaQbqY3jGLJxXm3ux8Ua package directory (directory-1.3.0.2-7PuJPOCiLbC9oRaTNsfccX) requires Win32-2.5.4.1-8epaQbqY3jGLJxXm3ux8Ua package ghci (ghci-8.2.0.20170507) requires array-0.5.1.2 package ghc (ghc-8.2.0.20170507) requires array-0.5.1.2 package deepseq (deepseq-1.4.3.0) requires array-0.5.1.2 package containers (containers-0.5.10.2) requires array-0.5.1.2 package binary (binary-0.8.5.1) requires array-0.5.1.2 package type-tensor (type-tensor-0.1.0.0) requires array-0.5.1.2-HLhzmZOrFF33n5vNRSsiul package text (text-1.2.2.2-C576mx40Etr4P9ekPR0dZa) requires array-0.5.1.2-HLhzmZOrFF33n5vNRSsiul package integer-logarithms (integer- logarithms-1.0.1-J81sJnt8kMJ9jRMUf4vFoR) requires array-0.5.1.2-HLhzmZOrFF33n5vNRSsiul package deepseq (deepseq-1.4.3.0-1LQl7dQqRaX7SddkECLIDI) requires array-0.5.1.2-HLhzmZOrFF33n5vNRSsiul package containers (containers-0.5.7.1-JQ6HxxqcTn7Hov4MCJUivJ) requires array-0.5.1.2-HLhzmZOrFF33n5vNRSsiul package binary (binary-0.8.5.1-C4OPHIQcyRaGV2kWdJl2VT) requires array-0.5.1.2-HLhzmZOrFF33n5vNRSsiul package attoparsec (attoparsec-0.13.1.0-FUS3j19YAjQ6jq7Rnfohq) requires array-0.5.1.2-HLhzmZOrFF33n5vNRSsiul package ghci (ghci-8.2.0.20170507) requires binary-0.8.5.1 package ghc-boot (ghc-boot-8.2.0.20170507) requires binary-0.8.5.1 package ghc (ghc-8.2.0.20170507) requires binary-0.8.5.1 package uuid-types (uuid-types-1.0.3-K55Ih5xEU247FankRMW0NM) requires binary-0.8.5.1-C4OPHIQcyRaGV2kWdJl2VT package text (text-1.2.2.2-C576mx40Etr4P9ekPR0dZa) requires binary-0.8.5.1-C4OPHIQcyRaGV2kWdJl2VT package scientific (scientific-0.3.4.15-7PyzWbTeymdIyGs7DQZDDY) requires binary-0.8.5.1-C4OPHIQcyRaGV2kWdJl2VT package ghci (ghci-8.2.0.20170507) requires bytestring-0.10.8.2 package ghc-boot (ghc-boot-8.2.0.20170507) requires bytestring-0.10.8.2 package ghc (ghc-8.2.0.20170507) requires bytestring-0.10.8.2 package binary (binary-0.8.5.1) requires bytestring-0.10.8.2 package Win32 (Win32-2.5.4.1) requires bytestring-0.10.8.2 package uuid-types (uuid-types-1.0.3-K55Ih5xEU247FankRMW0NM) requires bytestring-0.10.8.2-HmJDVybICq95XgdDM4QLKI package text (text-1.2.2.2-C576mx40Etr4P9ekPR0dZa) requires bytestring-0.10.8.2-HmJDVybICq95XgdDM4QLKI package scientific (scientific-0.3.4.15-7PyzWbTeymdIyGs7DQZDDY) requires bytestring-0.10.8.2-HmJDVybICq95XgdDM4QLKI package hashable (hashable-1.2.6.0-JYQFWiKYG1UDI9NcuUwIS5) requires bytestring-0.10.8.2-HmJDVybICq95XgdDM4QLKI package dump-core (dump-core-0.1.3-G8qMx3XDmny68ZAiu2ZEKo) requires bytestring-0.10.8.2-HmJDVybICq95XgdDM4QLKI package binary (binary-0.8.5.1-C4OPHIQcyRaGV2kWdJl2VT) requires bytestring-0.10.8.2-HmJDVybICq95XgdDM4QLKI package attoparsec (attoparsec-0.13.1.0-FUS3j19YAjQ6jq7Rnfohq) requires bytestring-0.10.8.2-HmJDVybICq95XgdDM4QLKI package aeson (aeson-1.1.2.0-9gz0GeJuooI5cNB8Jm3VaT) requires bytestring-0.10.8.2-HmJDVybICq95XgdDM4QLKI package Win32 (Win32-2.5.4.1-8epaQbqY3jGLJxXm3ux8Ua) requires bytestring-0.10.8.2-HmJDVybICq95XgdDM4QLKI package hpc (hpc-0.6.0.3) requires containers-0.5.10.2 package hoopl (hoopl-3.10.2.2) requires containers-0.5.10.2 package ghci (ghci-8.2.0.20170507) requires containers-0.5.10.2 package ghc (ghc-8.2.0.20170507) requires containers-0.5.10.2 package binary (binary-0.8.5.1) requires containers-0.5.10.2 package scientific (scientific-0.3.4.15-7PyzWbTeymdIyGs7DQZDDY) requires containers-0.5.7.1-JQ6HxxqcTn7Hov4MCJUivJ package dump-core (dump-core-0.1.3-G8qMx3XDmny68ZAiu2ZEKo) requires containers-0.5.7.1-JQ6HxxqcTn7Hov4MCJUivJ package binary (binary-0.8.5.1-C4OPHIQcyRaGV2kWdJl2VT) requires containers-0.5.7.1-JQ6HxxqcTn7Hov4MCJUivJ package attoparsec (attoparsec-0.13.1.0-FUS3j19YAjQ6jq7Rnfohq) requires containers-0.5.7.1-JQ6HxxqcTn7Hov4MCJUivJ package aeson (aeson-1.1.2.0-9gz0GeJuooI5cNB8Jm3VaT) requires containers-0.5.7.1-JQ6HxxqcTn7Hov4MCJUivJ package time (time-1.8.0.1) requires deepseq-1.4.3.0 package process (process-1.6.0.0) requires deepseq-1.4.3.0 package pretty (pretty-1.1.3.3) requires deepseq-1.4.3.0 package ghci (ghci-8.2.0.20170507) requires deepseq-1.4.3.0 package ghc (ghc-8.2.0.20170507) requires deepseq-1.4.3.0 package containers (containers-0.5.10.2) requires deepseq-1.4.3.0 package bytestring (bytestring-0.10.8.2) requires deepseq-1.4.3.0 package vector (vector-0.12.0.1-EZRn7LVKnvJJeGsCj3bs9M) requires deepseq-1.4.3.0-1LQl7dQqRaX7SddkECLIDI package uuid-types (uuid-types-1.0.3-K55Ih5xEU247FankRMW0NM) requires deepseq-1.4.3.0-1LQl7dQqRaX7SddkECLIDI package unordered-containers (unordered- containers-0.2.8.0-9DG9g9mCNzf2q6WCRkUFS4) requires deepseq-1.4.3.0-1LQl7dQqRaX7SddkECLIDI package time (time-1.8.0.1-7Vbd89jgVoWBI75ow03wJC) requires deepseq-1.4.3.0-1LQl7dQqRaX7SddkECLIDI package text (text-1.2.2.2-C576mx40Etr4P9ekPR0dZa) requires deepseq-1.4.3.0-1LQl7dQqRaX7SddkECLIDI package tagged (tagged-0.8.5-Kprpkqx3zNrJScWjBTq820) requires deepseq-1.4.3.0-1LQl7dQqRaX7SddkECLIDI package scientific (scientific-0.3.4.15-7PyzWbTeymdIyGs7DQZDDY) requires deepseq-1.4.3.0-1LQl7dQqRaX7SddkECLIDI package hashable (hashable-1.2.6.0-JYQFWiKYG1UDI9NcuUwIS5) requires deepseq-1.4.3.0-1LQl7dQqRaX7SddkECLIDI package dlist (dlist-0.8.0.2-GbiPGq2orrp5Ip3NNjwkmD) requires deepseq-1.4.3.0-1LQl7dQqRaX7SddkECLIDI package containers (containers-0.5.7.1-JQ6HxxqcTn7Hov4MCJUivJ) requires deepseq-1.4.3.0-1LQl7dQqRaX7SddkECLIDI package bytestring (bytestring-0.10.8.2-HmJDVybICq95XgdDM4QLKI) requires deepseq-1.4.3.0-1LQl7dQqRaX7SddkECLIDI package attoparsec (attoparsec-0.13.1.0-FUS3j19YAjQ6jq7Rnfohq) requires deepseq-1.4.3.0-1LQl7dQqRaX7SddkECLIDI package aeson (aeson-1.1.2.0-9gz0GeJuooI5cNB8Jm3VaT) requires deepseq-1.4.3.0-1LQl7dQqRaX7SddkECLIDI package process (process-1.6.0.0) requires directory-1.3.0.2 package hpc (hpc-0.6.0.3) requires directory-1.3.0.2 package ghc-boot (ghc-boot-8.2.0.20170507) requires directory-1.3.0.2 package ghc (ghc-8.2.0.20170507) requires directory-1.3.0.2 package dump-core (dump-core-0.1.3-G8qMx3XDmny68ZAiu2ZEKo) requires directory-1.3.0.2-7PuJPOCiLbC9oRaTNsfccX package process (process-1.6.0.0) requires filepath-1.4.1.2 package hpc (hpc-0.6.0.3) requires filepath-1.4.1.2 package ghci (ghci-8.2.0.20170507) requires filepath-1.4.1.2 package ghc-boot (ghc-boot-8.2.0.20170507) requires filepath-1.4.1.2 package ghc (ghc-8.2.0.20170507) requires filepath-1.4.1.2 package directory (directory-1.3.0.2) requires filepath-1.4.1.2 package Win32 (Win32-2.5.4.1) requires filepath-1.4.1.2 package dump-core (dump-core-0.1.3-G8qMx3XDmny68ZAiu2ZEKo) requires filepath-1.4.1.2-FVx4R9yeJjI1Ab4DPhTPDl package directory (directory-1.3.0.2-7PuJPOCiLbC9oRaTNsfccX) requires filepath-1.4.1.2-FVx4R9yeJjI1Ab4DPhTPDl package Win32 (Win32-2.5.4.1-8epaQbqY3jGLJxXm3ux8Ua) requires filepath-1.4.1.2-FVx4R9yeJjI1Ab4DPhTPDl package hpc (hpc-0.6.0.3) requires time-1.8.0.1 package ghc (ghc-8.2.0.20170507) requires time-1.8.0.1 package directory (directory-1.3.0.2) requires time-1.8.0.1 package time-locale-compat (time-locale- compat-0.1.1.3-ADr89HVPhNu71NOppkwVdg) requires time-1.8.0.1-7Vbd89jgVoWBI75ow03wJC package random (random-1.1-GLIzFPLOiIE1BNNTGq3j7b) requires time-1.8.0.1-7Vbd89jgVoWBI75ow03wJC package directory (directory-1.3.0.2-7PuJPOCiLbC9oRaTNsfccX) requires time-1.8.0.1-7Vbd89jgVoWBI75ow03wJC package aeson (aeson-1.1.2.0-9gz0GeJuooI5cNB8Jm3VaT) requires time-1.8.0.1-7Vbd89jgVoWBI75ow03wJC type-tensor-0.1.0.0: build (lib) Preprocessing library for type-tensor-0.1.0.0.. Building library for type-tensor-0.1.0.0.. [1 of 2] Compiling Data.Tensor ( src\Data\Tensor.hs, .stack- work\dist\f42fcbca\build\Data\Tensor.o ) GHC runtime linker: fatal error: I found a duplicate definition for symbol fps_reverse whilst processing object file C:\Users\darwi\Projects\type-tensor\.stack- work\install\0fd0aaa2\lib\x86_64-windows- ghc-8.2.0.20170507\bytestring-0.10.8.2-HmJDVybICq95XgdDM4QLKI\HSbytestring-0.10.8.2-HmJDVybICq95XgdDM4QLKI.o The symbol was previously defined in C:\Users\darwi\AppData\Local\Programs\stack\x86_64-windows\ghc-8.2.0.20170507\lib\bytestring-0.10.8.2\HSbytestring-0.10.8.2.o This could be caused by: * Loading two different object files which export the same symbol * Specifying the same object file twice on the GHCi command line * An incorrect `package.conf' entry, causing some object to be loaded twice. ghc.EXE: panic! (the 'impossible' happened) (GHC version 8.2.0.20170507 for x86_64-unknown-mingw32): loadObj "C:\\Users\\darwi\\Projects\\type-tensor\\.stack- work\\install\\0fd0aaa2\\lib\\x86_64-windows- ghc-8.2.0.20170507\\bytestring-0.10.8.2-HmJDVybICq95XgdDM4QLKI\\HSbytestring-0.10.8.2-HmJDVybICq95XgdDM4QLKI.o": failed Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug Completed 24 action(s). }}} These are the packages that I've added as extra dependencies. {{{ extra-deps: - dump-core-0.1.3 - deepseq-1.4.3.0 - hashable-1.2.6.0 - bytestring-0.10.8.2 - Win32-2.5.4.1 - array-0.5.1.2 - binary-0.8.5.1 - containers-0.5.7.1 - directory-1.3.0.2 - filepath-1.4.1.2 - time-1.8.0.1 }}} Any ideas? Also, I hope I'm not taking too much of anybody's time. Sorry guys. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jun 28 22:06:35 2017 From: ghc-devs at haskell.org (GHC) Date: Wed, 28 Jun 2017 22:06:35 -0000 Subject: [GHC] #9588: Add `MonadPlus (Either e)` and `Alternative (Either e)` instances In-Reply-To: <042.81b9305fea59cb0eb6b8168a5d80498d@haskell.org> References: <042.81b9305fea59cb0eb6b8168a5d80498d@haskell.org> Message-ID: <057.ce8be60458ed9f718b74f008fae77e9b@haskell.org> #9588: Add `MonadPlus (Either e)` and `Alternative (Either e)` instances -------------------------------------+------------------------------------- Reporter: hvr | Owner: hvr Type: task | Status: new Priority: normal | Milestone: ⊥ Component: Core Libraries | Version: Resolution: | Keywords: report-impact Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #10755 #12160 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by ekmett): Sadly. The current Error based instance in transformers is somewhat lacking in this and other regards. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jun 28 22:16:58 2017 From: ghc-devs at haskell.org (GHC) Date: Wed, 28 Jun 2017 22:16:58 -0000 Subject: [GHC] #13848: Unexpected order of variable quantification with GADT constructor In-Reply-To: <050.1bdc037c5d3daf9f53281904769def22@haskell.org> References: <050.1bdc037c5d3daf9f53281904769def22@haskell.org> Message-ID: <065.b7e9c24b383071d5ddb8b1e64f4ddca8@haskell.org> #13848: Unexpected order of variable quantification with GADT constructor -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.1 checker) | Keywords: Resolution: | TypeApplications Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): Yes you are right. So yes, we have to put more info in the `IfaceConDecl`. Putting in the wrapper type doesn't feel right -- duplicates too much. Better to put in the original tyvars. And in that case we may as well record them in the `DataCon` too, as you suggested earlier. Then we wouldn't need to pass them to `mkDataConRep` after all, because they'll be in the `DataCon`. One fiddly thing I'm not sure about: in the declaration of `IfaceConDecl` we see {{{ data IfaceConDecl = IfCon { ifConName :: IfaceTopBndr, -- Constructor name ifConWrapper :: Bool, -- True <=> has a wrapper ifConInfix :: Bool, -- True <=> declared infix -- The universal type variables are precisely those -- of the type constructor of this data constructor -- This is *easy* to guarantee when creating the IfCon -- but it's not so easy for the original TyCon/DataCon -- So this guarantee holds for IfaceConDecl, but *not* for DataCon }}} Reasoning is explained in `MkIface` where we convert a `DataCon` to a `ConDecl` {{{ -- Tidy the univ_tvs of the data constructor to be identical -- to the tyConTyVars of the type constructor. This means -- (a) we don't need to redundantly put them into the interface file -- (b) when pretty-printing an Iface data declaration in H98-style syntax, -- we know that the type variables will line up -- The latter (b) is important because we pretty-print type constructors -- by converting to IfaceSyn and pretty-printing that con_env1 = (fst tc_env1, mkVarEnv (zipEqual "ifaceConDecl" univ_tvs tc_tyvars)) -- A bit grimy, perhaps, but it's simple! }}} Meddling with `IfaceConDecl` is not a big deal... it's just a serialisation format, and changes are very localised. So feel free to suggest what to do. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jun 28 23:23:30 2017 From: ghc-devs at haskell.org (GHC) Date: Wed, 28 Jun 2017 23:23:30 -0000 Subject: [GHC] #13886: GHC panic when using GHC plugins In-Reply-To: <048.4e65bf02b6c4ff69cd509bbe731fe7ea@haskell.org> References: <048.4e65bf02b6c4ff69cd509bbe731fe7ea@haskell.org> Message-ID: <063.f6c01bc92f41f37b1decb76ed9b2fbf4@haskell.org> #13886: GHC panic when using GHC plugins -------------------------------------+------------------------------------- Reporter: Darwin226 | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.2 Resolution: | Keywords: Operating System: Windows | Architecture: x86_64 Type of failure: Compile-time | (amd64) crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): Urgh. Reasons like this is why I find testing GHC HEAD with `stack` to be infuriating. If you really must use `stack`, my guess is that adding dependencies of the `ghc` library (e.g., `bytestring`) to `extra-deps` is confusing it and causing it to link against two different copies of the same library, causing linker shenanigans. What happens if you remove everything except `dump-core`, `deepseq`, and `hashable`? When I get a chance, I'll try installing `dump-core` myself on my Windows machine with `cabal-install` (if someone else doesn't do so before me). -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jun 29 05:35:52 2017 From: ghc-devs at haskell.org (GHC) Date: Thu, 29 Jun 2017 05:35:52 -0000 Subject: [GHC] #13894: isByteArrayPinned# should consider BF_LARGE Message-ID: <045.c57512fc5db0ab6f4b4f6b7f8600318c@haskell.org> #13894: isByteArrayPinned# should consider BF_LARGE -------------------------------------+------------------------------------- Reporter: winter | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- First of all, i want to make sure `isByteArrayPinned#` is intended to let user know if a given 'ByteArray#/MutableByteArray#' is movable during safe FFI call, isn't it? If that is the case, then the code for `stg_isByteArrayPinnedzh` is not enough, since not only bytes marked with `BF_PINNED` flag is not movable, but also the bytes which is marked with `BF_LARGE`. (I read the gc code and i'm confident this holds, but if it's not, please correct me). Currently i'm using a FFI trick[https://github.com/winterland1989/stdio/blob/master/cbits/bytes.c#L33] to get `isByteArrayPinned#` on older GHCs, i want to make sure if `BF_LARGE` works. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jun 29 06:21:55 2017 From: ghc-devs at haskell.org (GHC) Date: Thu, 29 Jun 2017 06:21:55 -0000 Subject: [GHC] #13535: vector test suite uses excessive memory on GHC 8.2 In-Reply-To: <050.16d8aabc8a5c61d8950e3575a8e4ccd4@haskell.org> References: <050.16d8aabc8a5c61d8950e3575a8e4ccd4@haskell.org> Message-ID: <065.d8952f6b81a3cd7c94b256d03dc82ea1@haskell.org> #13535: vector test suite uses excessive memory on GHC 8.2 -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: bgamari Type: bug | Status: new Priority: highest | Milestone: 8.2.1 Component: Compiler | Version: 8.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: #10800 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by dfeuer): FWIW, this is what I see on HEAD right now, compiling with {{{ ~/src/ghc-clean-june28/inplace/bin/ghc-stage2 -no-link -fbuilding-cabal- package -static -dynamic-too -dynosuf dyn_o -dynhisuf dyn_hi -outputdir dist/build/vector-tests-O2/vector-tests-O2-tmp -odir dist/build/vector- tests-O2/vector-tests-O2-tmp -hidir dist/build/vector-tests-O2/vector- tests-O2-tmp -stubdir dist/build/vector-tests-O2/vector-tests-O2-tmp -i -idist/build/vector-tests-O2/vector-tests-O2-tmp -itests -idist/build/autogen -Idist/build/autogen -Idist/build/vector-tests-O2 /vector-tests-O2-tmp -optP-include -optPdist/build/autogen/cabal_macros.h -hide-all-packages -package-db dist/package.conf.inplace -package HUnit-1.6.0.0 -package QuickCheck-2.9.2 -package base -package random-1.1 -package template-haskell -package test-framework-0.8.1.1 -package test- framework-hunit-0.3.0.2 -package test-framework-quickcheck2-0.3.0.3 -package transformers-0.5.2.0 -package vector-0.12.0.1 -XHaskell2010 -XCPP -XScopedTypeVariables -XPatternGuards -XMultiParamTypeClasses -XFlexibleContexts -XRank2Types -XTypeSynonymInstances -XTypeFamilies -XTemplateHaskell tests/Tests/Vector.hs -O2 -fno-warn-orphans -fno-warn- missing-signatures -Rghc-timing }}} {{{ DV Bool: <> DV Int: <> DVP Int: <> DVP Double: <> DVS Int: <> DVS Double: <> DVU (): <> DVU Bool: <> DVU Int: <> DVU Double: <> DVU (Int, Bool): <> DVU (Int, Bool, Int): <> Total allocations for all individual: 250492415944 all together: <> }}} So it currently allocates somewhat less compiling all together than compiling separately. bgamari's table for 8.0.2 looks like it has the wrong number for the "all together" case, so I'm not sure how to compare. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jun 29 09:12:13 2017 From: ghc-devs at haskell.org (GHC) Date: Thu, 29 Jun 2017 09:12:13 -0000 Subject: [GHC] #9588: Add `MonadPlus (Either e)` and `Alternative (Either e)` instances In-Reply-To: <042.81b9305fea59cb0eb6b8168a5d80498d@haskell.org> References: <042.81b9305fea59cb0eb6b8168a5d80498d@haskell.org> Message-ID: <057.5343df67970ea002f85aaac4d0e9b559@haskell.org> #9588: Add `MonadPlus (Either e)` and `Alternative (Either e)` instances -------------------------------------+------------------------------------- Reporter: hvr | Owner: hvr Type: task | Status: new Priority: normal | Milestone: ⊥ Component: Core Libraries | Version: Resolution: | Keywords: report-impact Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #10755 #12160 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Iceland_jack): Replying to [comment:12 ekmett]: > Sadly. > > The current Error based instance in transformers is somewhat lacking in this and other regards. I mindlessly applied that and it broke a parser in our code :) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jun 29 10:20:21 2017 From: ghc-devs at haskell.org (GHC) Date: Thu, 29 Jun 2017 10:20:21 -0000 Subject: [GHC] #13875: ApplicativeDo desugaring is lazier than standard desugaring In-Reply-To: <045.2eda858359df0999208d04da5f95a1da@haskell.org> References: <045.2eda858359df0999208d04da5f95a1da@haskell.org> Message-ID: <060.21748ef4791b8ae9408c84d1773e22d0@haskell.org> #13875: ApplicativeDo desugaring is lazier than standard desugaring -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: simonmar Type: bug | Status: new Priority: high | Milestone: 8.2.1 Component: Compiler | Version: 8.3 Resolution: | Keywords: ApplicativeDo Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Other | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3681 Wiki Page: | -------------------------------------+------------------------------------- Comment (by Iceland_jack): I have long had an idea for an `ado`, restricting the `do`-notation to be `Applicative` or weaker. It would make the user intent's clearer, "this should not have a `Monad` constraint" and paves the way for a wealth of Shakespearean puns -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jun 29 13:05:03 2017 From: ghc-devs at haskell.org (GHC) Date: Thu, 29 Jun 2017 13:05:03 -0000 Subject: [GHC] #13891: forkIO can trivially defeat bracket In-Reply-To: <046.bb2170e97e55c0c11118313e8136933d@haskell.org> References: <046.bb2170e97e55c0c11118313e8136933d@haskell.org> Message-ID: <061.38dfdf675b83e2579fe1af83e352e9d4@haskell.org> #13891: forkIO can trivially defeat bracket -------------------------------------+------------------------------------- Reporter: bgamari | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * cc: Jaffacake (added) Comment: Simon, what is the recommended way of dealing with this? It seems to me like this should be considered a bug and we should throw exceptions to threads before terminating. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jun 29 14:31:05 2017 From: ghc-devs at haskell.org (GHC) Date: Thu, 29 Jun 2017 14:31:05 -0000 Subject: [GHC] #13881: Inexplicable error message when using out-of-scope type variable in pattern type signature In-Reply-To: <050.64fe59f3330624a2ee7d23968276dcc1@haskell.org> References: <050.64fe59f3330624a2ee7d23968276dcc1@haskell.org> Message-ID: <065.7270e030e2fcf44d5eb39c3028833c2b@haskell.org> #13881: Inexplicable error message when using out-of-scope type variable in pattern type signature -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.1 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Poor/confusing | Unknown/Multiple error message | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Simon Peyton Jones ): In [changeset:"3b0e7555fafe73b157a96ca48d8ddc04ad81b231/ghc" 3b0e7555/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="3b0e7555fafe73b157a96ca48d8ddc04ad81b231" Fix lexically-scoped type variables Trac #13881 showed that our handling of lexically scoped type variables was way off when we bring into scope a name 'y' for a pre-existing type variable 'a', perhaps with an entirely different name. This patch fixes it; see TcHsType Note [Pattern signature binders] }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jun 29 14:32:19 2017 From: ghc-devs at haskell.org (GHC) Date: Thu, 29 Jun 2017 14:32:19 -0000 Subject: [GHC] #13881: Inexplicable error message when using out-of-scope type variable in pattern type signature In-Reply-To: <050.64fe59f3330624a2ee7d23968276dcc1@haskell.org> References: <050.64fe59f3330624a2ee7d23968276dcc1@haskell.org> Message-ID: <065.5861681572e09de785617f651f497a2a@haskell.org> #13881: Inexplicable error message when using out-of-scope type variable in pattern type signature -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: merge Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.1 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Poor/confusing | Test Case: error message | typecheck/should_compile/T13881 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * status: new => merge * testcase: => typecheck/should_compile/T13881 Comment: Great diagnosis, as ever. All fixed. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jun 29 14:44:07 2017 From: ghc-devs at haskell.org (GHC) Date: Thu, 29 Jun 2017 14:44:07 -0000 Subject: [GHC] #13881: Inexplicable error message when using out-of-scope type variable in pattern type signature In-Reply-To: <050.64fe59f3330624a2ee7d23968276dcc1@haskell.org> References: <050.64fe59f3330624a2ee7d23968276dcc1@haskell.org> Message-ID: <065.1332e9db8491f612788f2d2ac77f2fab@haskell.org> #13881: Inexplicable error message when using out-of-scope type variable in pattern type signature -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: merge Priority: normal | Milestone: 8.2.1 Component: Compiler (Type | Version: 8.0.1 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Poor/confusing | Test Case: error message | typecheck/should_compile/T13881 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * milestone: => 8.2.1 Comment: Thanks, Simon! -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jun 29 15:42:08 2017 From: ghc-devs at haskell.org (GHC) Date: Thu, 29 Jun 2017 15:42:08 -0000 Subject: [GHC] #13895: "Illegal constraint in a type" error - is it fixable? Message-ID: <050.ce595caa9b871911009a7eed084d4706@haskell.org> #13895: "Illegal constraint in a type" error - is it fixable? -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 (Type checker) | Keywords: TypeInType | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- I recently sketched out a solution to #13327. Here is the type signature that I wanted to write: {{{#!hs dataCast1 :: forall (c :: Type -> Type) (t :: forall (k :: Type). k -> Type). Typeable t => (forall d. Data d => c (t d)) -> Maybe (c a) }}} But this doesn't typecheck: {{{ • Could not deduce (Typeable (t k0)) from the context: (Data a, Typeable (t k)) bound by the type signature for: dataCast1 :: forall a. Data a => forall k (c :: * -> *) (t :: forall k1. k1 -> *). Typeable (t k) => (forall d. Data d => c (t * d)) -> Maybe (c a) at NewData.hs:(170,3)-(173,26) The type variable ‘k0’ is ambiguous • In the ambiguity check for ‘dataCast1’ To defer the ambiguity check to use sites, enable AllowAmbiguousTypes When checking the class method: dataCast1 :: forall a. Data a => forall k (c :: * -> *) (t :: forall k1. k1 -> *). Typeable (t k) => (forall d. Data d => c (t * d)) -> Maybe (c a) In the class declaration for ‘Data’ | 170 | dataCast1 :: forall (c :: Type -> Type) (t :: forall (k :: Type). k -> Type). | ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^... }}} This makes sense, since GHC has no way to conclude that the `k` in `t`'s kind is also `Typeable`. I tried to convince GHC of that fact: {{{#!hs dataCast1 :: forall (c :: Type -> Type) (t :: forall (k :: Type). Typeable k => k -> Type). Typeable t => (forall d. Data d => c (t d)) -> Maybe (c a) }}} But this also doesn't work: {{{ NewData.hs:171:25: error: • Illegal constraint in a type: Typeable k0 • In the first argument of ‘Typeable’, namely ‘t’ In the type signature: dataCast1 :: forall (c :: Type -> Type) (t :: forall (k :: Type). Typeable k => k -> Type). Typeable t => (forall d. Data d => c (t d)) -> Maybe (c a) In the class declaration for ‘Data’ | 171 | Typeable t | ^ NewData.hs:172:40: error: • Illegal constraint in a type: Typeable k0 • In the first argument of ‘c’, namely ‘(t d)’ In the type signature: dataCast1 :: forall (c :: Type -> Type) (t :: forall (k :: Type). Typeable k => k -> Type). Typeable t => (forall d. Data d => c (t d)) -> Maybe (c a) In the class declaration for ‘Data’ | 172 | => (forall d. Data d => c (t d)) | ^^^ }}} At this point, I'm stuck, since I have no idea how to work around this `Illegal constraint in a type` error. This error message appears to have originated as a part of the `TypeInType` patch, since there's even a [http://git.haskell.org/ghc.git/blob/58c781da4861faab11e4c5804e07e6892908ef72:/testsuite/tests/dependent/should_fail/PromotedClass.hs test case] checking for this behavior. But is this a fundamental limitation of kind equalities? Or would it be possible to lift this restriction? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jun 29 15:44:51 2017 From: ghc-devs at haskell.org (GHC) Date: Thu, 29 Jun 2017 15:44:51 -0000 Subject: [GHC] #13896: Use response file to invoke hsc2hs Message-ID: <046.8d005e1593e32147d596c190fbabb716@haskell.org> #13896: Use response file to invoke hsc2hs ----------------------------------------+--------------------------------- Reporter: bgamari | Owner: (none) Type: bug | Status: new Priority: high | Milestone: 8.4.1 Component: hsc2hs | Version: 8.0.1 Keywords: | Operating System: Windows Architecture: Unknown/Multiple | Type of failure: None/Unknown Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: ----------------------------------------+--------------------------------- We already use response files when invoking Haddock due to Windows command line length limitations. It [[https://github.com/haskell/cabal/issues/3122#issuecomment-311489312|seems]] that we also need to do the same with `hsc2hs`. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jun 29 17:11:26 2017 From: ghc-devs at haskell.org (GHC) Date: Thu, 29 Jun 2017 17:11:26 -0000 Subject: [GHC] #13848: Unexpected order of variable quantification with GADT constructor In-Reply-To: <050.1bdc037c5d3daf9f53281904769def22@haskell.org> References: <050.1bdc037c5d3daf9f53281904769def22@haskell.org> Message-ID: <065.2d689fc36d2fef705e7116ec7e1f6ebf@haskell.org> #13848: Unexpected order of variable quantification with GADT constructor -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.1 checker) | Keywords: Resolution: duplicate | TypeApplications Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #11721 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * status: new => closed * resolution: => duplicate * related: => #11721 Comment: Oh dear, I just realized this is a duplicate of #11721. Closing in favor of that ticket. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jun 29 17:11:55 2017 From: ghc-devs at haskell.org (GHC) Date: Thu, 29 Jun 2017 17:11:55 -0000 Subject: [GHC] #11721: GADT-syntax data constructors don't work well with TypeApplications In-Reply-To: <047.d3cda57aa918919c3cdf02eb21c0a581@haskell.org> References: <047.d3cda57aa918919c3cdf02eb21c0a581@haskell.org> Message-ID: <062.c2553b8542e156fbf7d9be931198ceec@haskell.org> #11721: GADT-syntax data constructors don't work well with TypeApplications -------------------------------------+------------------------------------- Reporter: goldfire | Owner: goldfire Type: bug | Status: new Priority: normal | Milestone: 8.4.1 Component: Compiler | Version: 8.1 Resolution: | Keywords: | TypeApplications Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #13848 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * cc: RyanGlScott (added) * related: => #13848 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jun 29 17:43:58 2017 From: ghc-devs at haskell.org (GHC) Date: Thu, 29 Jun 2017 17:43:58 -0000 Subject: [GHC] #13893: Improved Help for Control.Concurrent and Control.Exception when "variable not in scope" In-Reply-To: <044.50a1c8e97ad1d72587a33a02855fe4cb@haskell.org> References: <044.50a1c8e97ad1d72587a33a02855fe4cb@haskell.org> Message-ID: <059.556f4a7e91690cfdeb07a54914e541b7@haskell.org> #13893: Improved Help for Control.Concurrent and Control.Exception when "variable not in scope" -------------------------------------+------------------------------------- Reporter: vanto | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Poor/confusing | Unknown/Multiple error message | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by vanto): Here I am talking about library that are natively in the compiler, of course, such as {{{Data.Char}}}. The principle would be identical to the suggestion of the pragmas to be used which are stated in the error message by the compiler.\\ This does not apply to library that are external to the compiler. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jun 29 18:22:14 2017 From: ghc-devs at haskell.org (GHC) Date: Thu, 29 Jun 2017 18:22:14 -0000 Subject: [GHC] #13897: Ship check-ppr in bindist and compile during testsuite run Message-ID: <046.c1d9498de95e82cc15e6c9fd657e4d84@haskell.org> #13897: Ship check-ppr in bindist and compile during testsuite run -------------------------------------+------------------------------------- Reporter: bgamari | Owner: (none) Type: task | Status: new Priority: normal | Milestone: 8.4.1 Component: Compiler | Version: 8.0.1 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- Currently `check-ppr` is built during the compiler build and used by the testsuite in the pretty-printer tests. In a source checkout this is fine, however this arrangement blows up in the case of a binary distribution as we don't (and probably shouldn't) ship the `check-ppr` binary in the bindist. I think the most reasonable way to deal with this is to instead ship the `check-ppr` source (perhaps in the testsuite tarball) and build it as a dependency of the testsuite. Ideally we would build the executable once and use it for each of the ppr tests. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jun 29 18:24:43 2017 From: ghc-devs at haskell.org (GHC) Date: Thu, 29 Jun 2017 18:24:43 -0000 Subject: [GHC] #13897: Ship check-ppr in bindist and compile during testsuite run In-Reply-To: <046.c1d9498de95e82cc15e6c9fd657e4d84@haskell.org> References: <046.c1d9498de95e82cc15e6c9fd657e4d84@haskell.org> Message-ID: <061.34e956edf584839d96fe5a8d9e1473b5@haskell.org> #13897: Ship check-ppr in bindist and compile during testsuite run -------------------------------------+------------------------------------- Reporter: bgamari | Owner: alanz Type: task | Status: new Priority: normal | Milestone: 8.4.1 Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by alanz): * owner: (none) => alanz Comment: I will give it a go. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jun 29 18:49:16 2017 From: ghc-devs at haskell.org (GHC) Date: Thu, 29 Jun 2017 18:49:16 -0000 Subject: [GHC] #9173: Better type error messages In-Reply-To: <046.f8f24aa2ddaa3d579bc40f0b6f04f6b7@haskell.org> References: <046.f8f24aa2ddaa3d579bc40f0b6f04f6b7@haskell.org> Message-ID: <061.dc24bdc160e759658f48695b8eda8629@haskell.org> #9173: Better type error messages -------------------------------------+------------------------------------- Reporter: simonpj | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.8.2 Resolution: | Keywords: | TypeErrorMessages Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by vanto): I'm coming back about the solution provided by rwbarton. This solution is not appropriate in the case below. {{{ let y = [True, 'a'] }}} What is the actual type? What is the expected type?\\ If I change the order of the values in the list like this: {{{ let y = ['a', True] }}} What is the actual type? What is the expected type?\\\\ An obvious answer is {{{The types must be identical in a list}}} or {{{The types are not equal}}} Here we see that there is no signature. If the signature had been {{{y :: [Char]}}} The obvious answer is the one I have given in comment 23, and which is {{{ The Type of the result is not in accordance with the Type of the signature }}} So I no longer agree with rwbarton and bgamari. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jun 29 19:38:26 2017 From: ghc-devs at haskell.org (GHC) Date: Thu, 29 Jun 2017 19:38:26 -0000 Subject: [GHC] #9173: Better type error messages In-Reply-To: <046.f8f24aa2ddaa3d579bc40f0b6f04f6b7@haskell.org> References: <046.f8f24aa2ddaa3d579bc40f0b6f04f6b7@haskell.org> Message-ID: <061.238857d49a2653d0b30ef7b9e6c9e6a0@haskell.org> #9173: Better type error messages -------------------------------------+------------------------------------- Reporter: simonpj | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.8.2 Resolution: | Keywords: | TypeErrorMessages Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by j.waldmann): Interesting, but I think this is a separate issue (type error message for list literals). `['a', True]` gets translated to `'a' : (True : [])`, see language spec 3.7. https://www.haskell.org/onlinereport/haskell2010/haskellch3.html#x8-340003.7 So there is no special rule for typing list literals, as the compiler checks the translated code anyway. Or so I thought, but in fact there is: after stating the translation, the standard states that in `[e1, ..., ek]`, "the types of e1 ... ek must all be the same". Is this normative, or just a (redundant) explanation? I do think that compiler (error) messages should use wording from the standard. (So, looking up words in OED does not really help. The committee that wrote the standard already did this.) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jun 29 20:19:57 2017 From: ghc-devs at haskell.org (GHC) Date: Thu, 29 Jun 2017 20:19:57 -0000 Subject: [GHC] #11409: Cannot instantiate literals using TypeApplications In-Reply-To: <048.6352883c4ebf7b6ed5ee4d78320dfea2@haskell.org> References: <048.6352883c4ebf7b6ed5ee4d78320dfea2@haskell.org> Message-ID: <063.3a4641f5413e88129971a8d0804e0642@haskell.org> #11409: Cannot instantiate literals using TypeApplications -------------------------------------+------------------------------------- Reporter: Feuerbach | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: 8.4.1 Component: Compiler | Version: 8.0.1-rc1 Resolution: | Keywords: | TypeApplications Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #11352 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Iceland_jack): Mentioned in [https://www.reddit.com/r/haskell/comments/6k86je/constraint_unions_bringing_or_to_the_language_of/djkmdbi/?utm_content=permalink&utm_medium=front&utm_source=reddit&utm_name=haskell reddit comment] > I keep being surprised/disappointed that I can't do `5 @Int` and have to do `(5 :: Int)` instead. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jun 29 20:51:59 2017 From: ghc-devs at haskell.org (GHC) Date: Thu, 29 Jun 2017 20:51:59 -0000 Subject: [GHC] #13893: Improved Help for Control.Concurrent and Control.Exception when "variable not in scope" In-Reply-To: <044.50a1c8e97ad1d72587a33a02855fe4cb@haskell.org> References: <044.50a1c8e97ad1d72587a33a02855fe4cb@haskell.org> Message-ID: <059.daf31b0062f3513680a05d240c68ba15@haskell.org> #13893: Improved Help for Control.Concurrent and Control.Exception when "variable not in scope" -------------------------------------+------------------------------------- Reporter: vanto | Owner: (none) Type: feature request | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 8.0.2 Resolution: wontfix | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Poor/confusing | Unknown/Multiple error message | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => closed * resolution: => wontfix Comment: As with #13883, I agree there is a problem here but don't believe the compiler is the right place to solve it. This is the exact sort of problem which you want external tooling to solve. Afterall, in the case of `cabal new-build` GHC doesn't even know of all of the packages available. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jun 29 20:54:14 2017 From: ghc-devs at haskell.org (GHC) Date: Thu, 29 Jun 2017 20:54:14 -0000 Subject: [GHC] #13884: To an automatic compilation of file-header LANGUAGE pragmas in GHC. In-Reply-To: <044.5438e0b55f2f96ccdf324b161ad363cb@haskell.org> References: <044.5438e0b55f2f96ccdf324b161ad363cb@haskell.org> Message-ID: <059.b05ab066be21098a875cf23c7121df7e@haskell.org> #13884: To an automatic compilation of file-header LANGUAGE pragmas in GHC. -------------------------------------+------------------------------------- Reporter: vanto | Owner: (none) Type: feature request | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 8.0.2 Resolution: wontfix | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Other | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => closed * resolution: => wontfix Comment: Feel free to write an external tool (perhaps linking against the `ghc` API) to perform the search that your propose. However, I don't believe the compiler is the right place for this sort of logic. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jun 29 21:24:16 2017 From: ghc-devs at haskell.org (GHC) Date: Thu, 29 Jun 2017 21:24:16 -0000 Subject: [GHC] #13594: Typechecker behavior w.r.t. BangPatterns and nested foralls has changed in 8.2 In-Reply-To: <050.d768cbcd7afd3c7633840a8a13d3da1c@haskell.org> References: <050.d768cbcd7afd3c7633840a8a13d3da1c@haskell.org> Message-ID: <065.079f12583e9c545b05377ff97e2581cc@haskell.org> #13594: Typechecker behavior w.r.t. BangPatterns and nested foralls has changed in 8.2 -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: bgamari Type: bug | Status: merge Priority: high | Milestone: 8.2.1 Component: Compiler (Type | Version: 8.2.1-rc2 checker) | Keywords: BangPatterns, Resolution: | RankNTypes Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3661 Wiki Page: | -------------------------------------+------------------------------------- Comment (by alanz): I can confirm that the API Annotations work fine with ghc-exactprint, as at https://github.com/alanz/ghc- exactprint/commit/bcc41d3ffd295312e05eb745a63464b505786cc1 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jun 29 21:32:32 2017 From: ghc-devs at haskell.org (GHC) Date: Thu, 29 Jun 2017 21:32:32 -0000 Subject: [GHC] #13898: Consolidate treatment of strictness in parser Message-ID: <046.1a0266a99db3886bbce417a249212d33@haskell.org> #13898: Consolidate treatment of strictness in parser -------------------------------------+------------------------------------- Reporter: bgamari | Owner: (none) Type: task | Status: new Priority: normal | Milestone: 8.4.1 Component: Compiler | Version: 8.0.1 (Parser) | Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- Currently GHC's treatment of binding strictness in the Haskell parser and AST is the result of a long, winding evolution. Since Phab:D3670 we have tracked strictness of variable bindings (e.g. `!x = ...`) in the `SrcStrictness` in `FunRhs` (see `Note [Varieties of bindings]`). This is parsed by ``. However, explicitly lazy bindings (e.g. `~x = ...`) are parsed via a completely different means (see the rule starting with `~` in `aexp`) and represented as `ELazyPat` until being mangled into a pattern in `RdrHsSyn`. It seems to me like these two paths should be more symmetric. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jun 29 21:43:12 2017 From: ghc-devs at haskell.org (GHC) Date: Thu, 29 Jun 2017 21:43:12 -0000 Subject: [GHC] #13899: Improve [-Wmissing-home-modules] error message Message-ID: <044.df49ba2605478e0a66697c9eebb1eedd@haskell.org> #13899: Improve [-Wmissing-home-modules] error message -------------------------------------+------------------------------------- Reporter: alanz | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.2.1 Component: Compiler | Version: 8.2.1-rc2 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- At the moment when this warning is triggered, GHC emits something like {{{#!hs : warning: [-Wmissing-home-modules] Modules are not listed in command line: Language.Haskell.GHC.ExactPrint }}} It is not clear that this is actually reporting a problem in the cabal file which has incomplete "other-modules" for one or other target. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jun 29 21:49:13 2017 From: ghc-devs at haskell.org (GHC) Date: Thu, 29 Jun 2017 21:49:13 -0000 Subject: [GHC] #13899: Improve [-Wmissing-home-modules] error message In-Reply-To: <044.df49ba2605478e0a66697c9eebb1eedd@haskell.org> References: <044.df49ba2605478e0a66697c9eebb1eedd@haskell.org> Message-ID: <059.6aa16a0b01b2c0d98107623f443242d9@haskell.org> #13899: Improve [-Wmissing-home-modules] error message -------------------------------------+------------------------------------- Reporter: alanz | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.2.1 Component: Compiler | Version: 8.2.1-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by hvr): As `-Wmissing-home-modules` is a generic warning message we may want to avoid mentioning `other-extensions` unless we're actually building via Cabal. So here's an example from `GhcMake.hs` which changes the compiler message based on the presence of the `-fcabal-building-package` flag: {{{#!hs in throwOneError $ mkPlainErrMsg dflags' mod_loc $ text "Unexpected signature:" <+> quotes (ppr mod_name) $$ if gopt Opt_BuildingCabalPackage dflags then parens (text "Try adding" <+> quotes (ppr mod_name) <+> text "to the" <+> quotes (text "signatures") <+> text "field in your Cabal file.") else parens (text "Try passing -instantiated-with=\"" <> suggested_instantiated_with <> text "\"" $$ text "replacing <" <> ppr mod_name <> text "> as necessary.") }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jun 29 22:12:56 2017 From: ghc-devs at haskell.org (GHC) Date: Thu, 29 Jun 2017 22:12:56 -0000 Subject: [GHC] #13894: isByteArrayPinned# should consider BF_LARGE In-Reply-To: <045.c57512fc5db0ab6f4b4f6b7f8600318c@haskell.org> References: <045.c57512fc5db0ab6f4b4f6b7f8600318c@haskell.org> Message-ID: <060.a6e6e310b583e9e0232dc1ad593f9bbe@haskell.org> #13894: isByteArrayPinned# should consider BF_LARGE -------------------------------------+------------------------------------- Reporter: winter | Owner: (none) Type: bug | Status: patch Priority: normal | Milestone: 8.4.1 Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3685 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => patch * differential: => Phab:D3685 * milestone: => 8.4.1 Comment: See Phab:D3685. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jun 29 22:19:05 2017 From: ghc-devs at haskell.org (GHC) Date: Thu, 29 Jun 2017 22:19:05 -0000 Subject: [GHC] #13594: Typechecker behavior w.r.t. BangPatterns and nested foralls has changed in 8.2 In-Reply-To: <050.d768cbcd7afd3c7633840a8a13d3da1c@haskell.org> References: <050.d768cbcd7afd3c7633840a8a13d3da1c@haskell.org> Message-ID: <065.663973aa327355c1b05ab2ae6345410b@haskell.org> #13594: Typechecker behavior w.r.t. BangPatterns and nested foralls has changed in 8.2 -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: bgamari Type: bug | Status: closed Priority: high | Milestone: 8.2.1 Component: Compiler (Type | Version: 8.2.1-rc2 checker) | Keywords: BangPatterns, Resolution: fixed | RankNTypes Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3661 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: merge => closed * resolution: => fixed Comment: Merged with c7ed911f1b102f85ba89fe2ccce9ecf8231d1b8c. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jun 29 22:19:26 2017 From: ghc-devs at haskell.org (GHC) Date: Thu, 29 Jun 2017 22:19:26 -0000 Subject: [GHC] #13871: GHC panic in 8.2 only: typeIsTypeable(Coercion) In-Reply-To: <050.f1a0fc44d1ac315eabed1b0be5437302@haskell.org> References: <050.f1a0fc44d1ac315eabed1b0be5437302@haskell.org> Message-ID: <065.adf5ea3465e40c5b2abb86e10a15ce6c@haskell.org> #13871: GHC panic in 8.2 only: typeIsTypeable(Coercion) -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: bgamari Type: bug | Status: closed Priority: high | Milestone: 8.2.1 Component: Compiler (Type | Version: 8.2.1-rc2 checker) | Keywords: TypeInType, Resolution: fixed | Typeable Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Compile-time | Test Case: crash or panic | typecheck/should_compile/T13871 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3671, Wiki Page: | Phab:D3672 -------------------------------------+------------------------------------- Changes (by bgamari): * status: merge => closed * resolution: => fixed Comment: Merged with 40cb68a606ceb082815b2452bfb4eac6ea57522b. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jun 29 22:20:24 2017 From: ghc-devs at haskell.org (GHC) Date: Thu, 29 Jun 2017 22:20:24 -0000 Subject: [GHC] #13541: Make it easier to use the gold linker In-Reply-To: <046.0b1321a637ed3292c60514e6510d2c09@haskell.org> References: <046.0b1321a637ed3292c60514e6510d2c09@haskell.org> Message-ID: <061.afe5798a28bb497f4a954f2620300382@haskell.org> #13541: Make it easier to use the gold linker -------------------------------------+------------------------------------- Reporter: bgamari | Owner: bgamari Type: feature request | Status: patch Priority: highest | Milestone: 8.2.1 Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #13810, #13739 | Differential Rev(s): Phab:D3449 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => patch -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jun 29 22:24:04 2017 From: ghc-devs at haskell.org (GHC) Date: Thu, 29 Jun 2017 22:24:04 -0000 Subject: [GHC] #13860: TODO: SMALL_MUT_ARR_PTRS in Compact.cmm In-Reply-To: <046.25ac2134055d26c6424aeecbae3f299a@haskell.org> References: <046.25ac2134055d26c6424aeecbae3f299a@haskell.org> Message-ID: <061.a3d59205de8ab67171e83a91fee79081@haskell.org> #13860: TODO: SMALL_MUT_ARR_PTRS in Compact.cmm -------------------------------------+------------------------------------- Reporter: bgamari | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.2.2 Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * milestone: 8.2.1 => 8.2.2 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jun 29 22:24:15 2017 From: ghc-devs at haskell.org (GHC) Date: Thu, 29 Jun 2017 22:24:15 -0000 Subject: [GHC] #13860: TODO: SMALL_MUT_ARR_PTRS in Compact.cmm In-Reply-To: <046.25ac2134055d26c6424aeecbae3f299a@haskell.org> References: <046.25ac2134055d26c6424aeecbae3f299a@haskell.org> Message-ID: <061.beda81e70510e61ff47bfc72b4ab12ff@haskell.org> #13860: TODO: SMALL_MUT_ARR_PTRS in Compact.cmm -------------------------------------+------------------------------------- Reporter: bgamari | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.2.2 Component: Compiler | Version: 8.2.1-rc1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * version: 8.0.1 => 8.2.1-rc1 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jun 29 22:24:43 2017 From: ghc-devs at haskell.org (GHC) Date: Thu, 29 Jun 2017 22:24:43 -0000 Subject: [GHC] #13220: Performance regressions in testsuite from join points In-Reply-To: <049.405b53d5bd8d89bbd89346c7b7cf9193@haskell.org> References: <049.405b53d5bd8d89bbd89346c7b7cf9193@haskell.org> Message-ID: <064.2adae73d1ae13a16bc85f21beed5f0c7@haskell.org> #13220: Performance regressions in testsuite from join points -------------------------------------+------------------------------------- Reporter: lukemaurer | Owner: rwbarton Type: bug | Status: closed Priority: normal | Milestone: 8.2.1 Component: Compiler | Version: 8.1 Resolution: fixed | Keywords: JoinPoints Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:3391 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => closed * resolution: => fixed -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jun 29 22:31:03 2017 From: ghc-devs at haskell.org (GHC) Date: Thu, 29 Jun 2017 22:31:03 -0000 Subject: [GHC] #13899: Improve [-Wmissing-home-modules] error message In-Reply-To: <044.df49ba2605478e0a66697c9eebb1eedd@haskell.org> References: <044.df49ba2605478e0a66697c9eebb1eedd@haskell.org> Message-ID: <059.e50914684c668cb002022af26f6156d3@haskell.org> #13899: Improve [-Wmissing-home-modules] error message -------------------------------------+------------------------------------- Reporter: alanz | Owner: (none) Type: bug | Status: patch Priority: normal | Milestone: 8.2.1 Component: Compiler | Version: 8.2.1-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3686 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => patch * differential: => Phab:D3686 Comment: See Phab:D3686. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jun 29 22:34:14 2017 From: ghc-devs at haskell.org (GHC) Date: Thu, 29 Jun 2017 22:34:14 -0000 Subject: [GHC] #13379: Space leak / quadratic behavior when inlining In-Reply-To: <048.3a3cc2c8142cd380727a72eb402237bb@haskell.org> References: <048.3a3cc2c8142cd380727a72eb402237bb@haskell.org> Message-ID: <063.add165af9bfd825cc8980577ab88da42@haskell.org> #13379: Space leak / quadratic behavior when inlining -------------------------------------+------------------------------------- Reporter: jberryman | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.2.2 Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Inlining Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Compile-time | Test Case: performance bug | perf/compile/T13379 Blocked By: | Blocking: Related Tickets: #13586 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * milestone: 8.2.1 => 8.2.2 Comment: dfeuer, could you open another ticket to track the remaining bits of this as suggested in comment:26 and close this? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jun 29 22:35:16 2017 From: ghc-devs at haskell.org (GHC) Date: Thu, 29 Jun 2017 22:35:16 -0000 Subject: [GHC] #13075: Top-level bang pattern accepted In-Reply-To: <047.f83b957eceda4fbb3c1b3de754ae577d@haskell.org> References: <047.f83b957eceda4fbb3c1b3de754ae577d@haskell.org> Message-ID: <062.2b44509ae266423c1e6046fc5a5eaa21@haskell.org> #13075: Top-level bang pattern accepted -------------------------------------+------------------------------------- Reporter: goldfire | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.2.2 Component: Compiler | Version: 8.0.1 (Parser) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | typecheck/should_fail/T13075 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * milestone: 8.2.1 => 8.2.2 Comment: I'm going to bump this off to 8.2.2 as it's a rather minor issue. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jun 29 22:40:49 2017 From: ghc-devs at haskell.org (GHC) Date: Thu, 29 Jun 2017 22:40:49 -0000 Subject: [GHC] #2988: Improve float-in In-Reply-To: <046.83e28bfdd70de8fbe4dfb2a2f0f105d9@haskell.org> References: <046.83e28bfdd70de8fbe4dfb2a2f0f105d9@haskell.org> Message-ID: <061.ad87bdeb44ea63dc472370522d46759f@haskell.org> #2988: Improve float-in -------------------------------------+------------------------------------- Reporter: simonpj | Owner: (none) Type: task | Status: new Priority: lowest | Milestone: 8.4.1 Component: Compiler | Version: 6.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * milestone: 8.2.1 => 8.4.1 @@ -2,1 +2,1 @@ - {{{ + {{{#!hs @@ -18,1 +18,1 @@ - {{{ + {{{#!hs @@ -26,1 +26,1 @@ - {{{ + {{{#!hs New description: At the moment we can get a cascade of simplifier iterations like this: {{{#!hs let x1 = blah x2 = x1 : [] x3 = 1 : x2 x4 = 2 : x3 in case blah of True -> f x4 False -> g x4 }}} Then `x4` satisfies the conditions for `postInlineUnconditionally` (not top-level, used once in each case branch, not inside lambda). So it's inlined. In the next iteration of the simplifier, `x3` satisfies the conditions, and so on. It might be better for `postUnconditionally` to require an interesting context. But then this case doesn't work so well: {{{#!hs let x = blah in case foo of { A -> ..x..; B -> ..x..; C -> ..no x.. } }}} If C is the hot branch, it's a good idea to push `x` into the A,B branches. But perhaps this question is one that `FloatIn` should deal with, not `postInlineUnconditionally`. Indeed `FloatIn` has the following comment: {{{#!hs -- For case expressions we duplicate the binding if it is -- reasonably small, and if it is not used in all the RHSs -- This is good for situations like -- let x = I# y in -- case e of -- C -> error x -- D -> error x -- E -> ...not mentioning x... }}} So this ticket is just to record the idea: * Make `postInlineUnconditionally` check for interesting context ...and check on performance changes, and whether `FloatIn` is doing the Right Thing. Simon -- -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jun 29 22:53:47 2017 From: ghc-devs at haskell.org (GHC) Date: Thu, 29 Jun 2017 22:53:47 -0000 Subject: [GHC] #13481: T12622 fails in ghci way In-Reply-To: <046.f9d04c6c728f8f80bc5f7c5da4765696@haskell.org> References: <046.f9d04c6c728f8f80bc5f7c5da4765696@haskell.org> Message-ID: <061.a4a456e911b7b70ad742063f43138967@haskell.org> #13481: T12622 fails in ghci way -------------------------------------+------------------------------------- Reporter: bgamari | Owner: bgamari Type: bug | Status: new Priority: high | Milestone: 8.2.2 Component: Compiler | Version: 8.1 Resolution: | Keywords: | StaticPointers Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: #12622 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * priority: normal => high * milestone: 8.2.1 => 8.2.2 Comment: I'm afraid this will need to wait for 8.2.2. Bumping priority to ensure I get to it. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jun 29 22:55:00 2017 From: ghc-devs at haskell.org (GHC) Date: Thu, 29 Jun 2017 22:55:00 -0000 Subject: [GHC] #13745: Investigate compile-time regressions in regex-tdfa-1.2.2 In-Reply-To: <046.b7de3eed99bc2dfd75756f4f73799d3c@haskell.org> References: <046.b7de3eed99bc2dfd75756f4f73799d3c@haskell.org> Message-ID: <061.43f8d1ec617a890b036bf51f811650e6@haskell.org> #13745: Investigate compile-time regressions in regex-tdfa-1.2.2 -------------------------------------+------------------------------------- Reporter: bgamari | Owner: (none) Type: task | Status: new Priority: high | Milestone: 8.2.2 Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * milestone: 8.2.1 => 8.2.2 Comment: This is certainly a significant regression, but I think it will need to wait until 8.2.2 at the earliest for resolution. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jun 29 22:55:54 2017 From: ghc-devs at haskell.org (GHC) Date: Thu, 29 Jun 2017 22:55:54 -0000 Subject: [GHC] #13610: Unhelpful error messages about lifted and unlifted types In-Reply-To: <046.43439217ad237220365df4287ab639e3@haskell.org> References: <046.43439217ad237220365df4287ab639e3@haskell.org> Message-ID: <061.e22ff633faeb988f679c7fc74085657a@haskell.org> #13610: Unhelpful error messages about lifted and unlifted types -------------------------------------+------------------------------------- Reporter: nomeata | Owner: (none) Type: bug | Status: new Priority: low | Milestone: 8.4.1 Component: Compiler (Type | Version: 8.1 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * milestone: 8.2.1 => 8.4.1 Comment: Bumping off to 8.4. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jun 29 23:12:53 2017 From: ghc-devs at haskell.org (GHC) Date: Thu, 29 Jun 2017 23:12:53 -0000 Subject: [GHC] #13900: Core lint in BuildFlavour=perf-llvm Message-ID: <046.659e0b338788e413a5940905a0f91074@haskell.org> #13900: Core lint in BuildFlavour=perf-llvm -------------------------------------+------------------------------------- Reporter: bgamari | Owner: (none) Type: bug | Status: new Priority: high | Milestone: 8.4.1 Component: Compiler | Version: 8.3 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: Compile-time Unknown/Multiple | crash or panic Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- I found the following Core lint failure when compiling c9977385dca9536f18374242f713b1048a38dec5 with `BuildFlavour=perf-llvm`, {{{ "inplace/bin/ghc-stage1" -hisuf dyn_hi -osuf dyn_o -hcsuf dyn_hc -fPIC -dynamic -O -H64m -fllvm -Wall -hide-all-packages -i -ighc/. -ighc/stage2/build -Ighc/stage2/build -ighc/stage2/build/ghc/autogen -Ighc/stage2/build/ghc/autogen -optP-DGHCI -optP-include -optPghc/stage2/build/ghc/autogen/cabal_macros.h -package-id base-4.10.0.0 -package-id array-0.5.1.2 -package-id bytestring-0.10.8.2 -package-id directory-1.3.0.2 -package-id process-1.6.0.0 -package-id filepath-1.4.1.2 -package-id ghc-boot-8.3 -package-id ghc-8.3 -package-id unix-2.7.2.2 -package-id containers-0.5.10.2 -package-id deepseq-1.4.3.0 -package-id ghci-8.3 -package-id haskeline-0.7.4.0 -package-id time-1.8.0.1 -package- id transformers-0.5.2.0 -Wall -fno-warn-name-shadowing -XHaskell2010 -O2 -dcore-lint -dcmm-lint -no-hs-main -threaded -no-user-package-db -rtsopts -Wnoncanonical-monad-instances -odir ghc/stage2/build -hidir ghc/stage2/build -stubdir ghc/stage2/build -c ghc/./GHCi/UI/Tags.hs -o ghc/stage2/build/GHCi/UI/Tags.dyn_o *** Core Lint errors : in result of Simplifier *** : warning: [RHS of $wgo_XtpE :: [Name] -> Session -> State# RealWorld -> (# State# RealWorld, [[TagInfo]] #)] Rule "SC:$wgo0": lhs type: (# State# RealWorld, [[TagInfo]] #) rhs type: (# State# RealWorld, [Maybe TyThing] #) *** Offending Program *** (see attached) }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jun 29 23:13:18 2017 From: ghc-devs at haskell.org (GHC) Date: Thu, 29 Jun 2017 23:13:18 -0000 Subject: [GHC] #13900: Core lint in BuildFlavour=perf-llvm In-Reply-To: <046.659e0b338788e413a5940905a0f91074@haskell.org> References: <046.659e0b338788e413a5940905a0f91074@haskell.org> Message-ID: <061.6a1f9f72767f1ee1b931ab5fda47d7e4@haskell.org> #13900: Core lint in BuildFlavour=perf-llvm -------------------------------------+------------------------------------- Reporter: bgamari | Owner: (none) Type: bug | Status: new Priority: high | Milestone: 8.4.1 Component: Compiler | Version: 8.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * Attachment "log.xz" added. Full compiler output -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jun 29 23:32:16 2017 From: ghc-devs at haskell.org (GHC) Date: Thu, 29 Jun 2017 23:32:16 -0000 Subject: [GHC] #13879: Strange interaction between higher-rank kinds and type synonyms In-Reply-To: <050.03cb88421049abbd653e9048089d3969@haskell.org> References: <050.03cb88421049abbd653e9048089d3969@haskell.org> Message-ID: <065.c1a83966fd877cad05c85a8952c2048b@haskell.org> #13879: Strange interaction between higher-rank kinds and type synonyms -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.2.1 Component: Compiler (Type | Version: 8.0.1 checker) | Resolution: fixed | Keywords: TypeInType Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: GHC rejects | Test Case: valid program | typecheck/should_compile/T13879 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: merge => closed * resolution: => fixed Comment: Merged in c1de0758157097c47de2787c46030174744422b6, 3fedc0fb5820243a1f47c883bb76b829a4a24c85, and 7d9ca50e184f2bc5da531646673fa7eecfd39862. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jun 29 23:32:41 2017 From: ghc-devs at haskell.org (GHC) Date: Thu, 29 Jun 2017 23:32:41 -0000 Subject: [GHC] #13881: Inexplicable error message when using out-of-scope type variable in pattern type signature In-Reply-To: <050.64fe59f3330624a2ee7d23968276dcc1@haskell.org> References: <050.64fe59f3330624a2ee7d23968276dcc1@haskell.org> Message-ID: <065.521fe9c7941914f916578c39a006cb4e@haskell.org> #13881: Inexplicable error message when using out-of-scope type variable in pattern type signature -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.2.1 Component: Compiler (Type | Version: 8.0.1 checker) | Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Poor/confusing | Test Case: error message | typecheck/should_compile/T13881 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: merge => closed * resolution: => fixed Comment: Merged in 2755f23919f7429668a933374f2a4ca14a9966b6. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jun 29 23:40:36 2017 From: ghc-devs at haskell.org (GHC) Date: Thu, 29 Jun 2017 23:40:36 -0000 Subject: [GHC] #13875: ApplicativeDo desugaring is lazier than standard desugaring In-Reply-To: <045.2eda858359df0999208d04da5f95a1da@haskell.org> References: <045.2eda858359df0999208d04da5f95a1da@haskell.org> Message-ID: <060.1231cd9bf22a959f7288c88ef27d4c81@haskell.org> #13875: ApplicativeDo desugaring is lazier than standard desugaring -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: simonmar Type: bug | Status: patch Priority: high | Milestone: 8.2.1 Component: Compiler | Version: 8.3 Resolution: | Keywords: ApplicativeDo Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Other | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3681 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => patch -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 30 00:02:22 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 30 Jun 2017 00:02:22 -0000 Subject: [GHC] #11721: GADT-syntax data constructors don't work well with TypeApplications In-Reply-To: <047.d3cda57aa918919c3cdf02eb21c0a581@haskell.org> References: <047.d3cda57aa918919c3cdf02eb21c0a581@haskell.org> Message-ID: <062.7c27ee5fae1489d2447ad84de7e454e2@haskell.org> #11721: GADT-syntax data constructors don't work well with TypeApplications -------------------------------------+------------------------------------- Reporter: goldfire | Owner: RyanGlScott Type: bug | Status: new Priority: normal | Milestone: 8.4.1 Component: Compiler | Version: 8.1 Resolution: | Keywords: | TypeApplications Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #13848 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * owner: goldfire => RyanGlScott Comment: I'm working on this at the moment. A very rough attempt at this is located at Phab:D3687, but it's nowhere near ready to be merged (the changes I've introduced bring out many inscrutable Core Lint errors, which I'll need to puzzle over). -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 30 00:18:21 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 30 Jun 2017 00:18:21 -0000 Subject: [GHC] #8281: The impossible happened: primRepToFFIType In-Reply-To: <044.47e20917996e473150de04c1ce1afc0b@haskell.org> References: <044.47e20917996e473150de04c1ce1afc0b@haskell.org> Message-ID: <059.c5c103531af6d3590aa1346ad52a3dfb@haskell.org> #8281: The impossible happened: primRepToFFIType -------------------------------------+------------------------------------- Reporter: tibbe | Owner: (none) Type: bug | Status: patch Priority: high | Milestone: 8.4.1 Component: Compiler | Version: 7.6.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3619 Wiki Page: | -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"7de2c07d61d8ff952164ee8e6948c1415514ee6d/ghc" 7de2c07d/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="7de2c07d61d8ff952164ee8e6948c1415514ee6d" users-guide: Document FFI safety guarantees Test Plan: Read it Reviewers: austin Subscribers: simonmar, rwbarton, thomie GHC Trac Issues: #13730, #8281 Differential Revision: https://phabricator.haskell.org/D3682 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 30 00:18:21 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 30 Jun 2017 00:18:21 -0000 Subject: [GHC] #13730: Running GLUT code in GHCi yields NSInternalInconsistencyException In-Reply-To: <050.f6283f68597bb13f67605132a145b9f1@haskell.org> References: <050.f6283f68597bb13f67605132a145b9f1@haskell.org> Message-ID: <065.b6307b18a8687b8aad21dc89d252cf96@haskell.org> #13730: Running GLUT code in GHCi yields NSInternalInconsistencyException --------------------------------+---------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.4.1 Component: GHCi | Version: 8.0.2 Resolution: fixed | Keywords: Operating System: MacOS X | Architecture: Unknown/Multiple Type of failure: GHCi crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | --------------------------------+---------------------------------------- Comment (by Ben Gamari ): In [changeset:"7de2c07d61d8ff952164ee8e6948c1415514ee6d/ghc" 7de2c07d/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="7de2c07d61d8ff952164ee8e6948c1415514ee6d" users-guide: Document FFI safety guarantees Test Plan: Read it Reviewers: austin Subscribers: simonmar, rwbarton, thomie GHC Trac Issues: #13730, #8281 Differential Revision: https://phabricator.haskell.org/D3682 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 30 00:18:21 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 30 Jun 2017 00:18:21 -0000 Subject: [GHC] #4210: LLVM: Dynamic Library Support In-Reply-To: <045.9da2e8588befc1a62c55be781a6ff87b@haskell.org> References: <045.9da2e8588befc1a62c55be781a6ff87b@haskell.org> Message-ID: <060.8d1c668b3df24e1a1a72a5ae429a4ca3@haskell.org> #4210: LLVM: Dynamic Library Support -------------------------------------+------------------------------------- Reporter: dterei | Owner: dterei Type: feature request | Status: closed Priority: low | Milestone: 7.6.2 Component: Compiler (LLVM) | Version: 6.13 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Runtime crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"6171b0b326e52221a0631cf75eb4866b36abe631/ghc" 6171b0b/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="6171b0b326e52221a0631cf75eb4866b36abe631" configure: Check for binutils #17166 This bug affects bfd ld on ARMv7, causing ld to incorrectly emit R_REL_COPY relocations, breaking tables-next-to-code. We've known about it for several years now and there is not yet a fix upstream. Previously we would simply force use of ld.gold on ARM. However, given the rework of linking configuration, I thought a more principled solution was in order. Test Plan: Validate on armv7 Reviewers: austin, hvr Subscribers: angerman, rwbarton, thomie, erikd GHC Trac Issues: #4210 Differential Revision: https://phabricator.haskell.org/D3676 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 30 00:18:21 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 30 Jun 2017 00:18:21 -0000 Subject: [GHC] #13883: T5435_dyn_asm fails with ld.gold In-Reply-To: <046.0650089fc873411130b9f2d72ad5ad9e@haskell.org> References: <046.0650089fc873411130b9f2d72ad5ad9e@haskell.org> Message-ID: <061.66936ab636649e90cfcc30da277202d7@haskell.org> #13883: T5435_dyn_asm fails with ld.gold -------------------------------------+------------------------------------- Reporter: bgamari | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"625143f473b58d770d2515b91c2566b52d35a4c3/ghc" 625143f4/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="625143f473b58d770d2515b91c2566b52d35a4c3" configure: Coerce gcc to use $LD instead of system default The configure script will now try to coerce gcc to use the linker pointed to by $LD instead of the system default (typically bfd ld). Moreover, we now check for `ld.gold` and `ld.lld` before trying `ld`. The previous behavior can be reverted to by using the new --disable-ld-override flag. On my machine gold seems to trigger an apparent infelicity in constructor behavior, causing T5435_asm to fail. I've opened #13883 to record this issue and have accepted the questionable constructor ordering for the time being. Test Plan: Validate with `config_args='--enable-ld-override'` Reviewers: austin, hvr, simonmar Subscribers: duog, nh2, rwbarton, thomie, erikd, snowleopard GHC Trac Issues: #13541, #13810, #13883 Differential Revision: https://phabricator.haskell.org/D3449 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 30 00:18:21 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 30 Jun 2017 00:18:21 -0000 Subject: [GHC] #13747: Can't use 'instance' keyword in associated type family instance In-Reply-To: <042.cfa21cd9140248a25075b778770d0326@haskell.org> References: <042.cfa21cd9140248a25075b778770d0326@haskell.org> Message-ID: <057.bc7745d300b19ca923d1a96e4f220e9c@haskell.org> #13747: Can't use 'instance' keyword in associated type family instance -------------------------------------+------------------------------------- Reporter: nh2 | Owner: erdeszt Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.2 Resolution: | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple error/warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3673 Wiki Page: | -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"007f255644f885d445e47e291e50eb12b5ecd08d/ghc" 007f255/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="007f255644f885d445e47e291e50eb12b5ecd08d" Allow optional instance keyword in associated type family instances Add the missing branch for parsing the optional 'instance' keyword in associated type family instance declarations. Fixes #13747 Reviewers: austin, bgamari Reviewed By: bgamari Subscribers: simonpj, RyanGlScott, rwbarton, thomie, mpickering Differential Revision: https://phabricator.haskell.org/D3673 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 30 00:18:21 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 30 Jun 2017 00:18:21 -0000 Subject: [GHC] #13810: Gold linker fails In-Reply-To: <045.174b108f34b20d346eba46d31b44114b@haskell.org> References: <045.174b108f34b20d346eba46d31b44114b@haskell.org> Message-ID: <060.3ef70c91d4f887b49ecb6d3f61afd3cf@haskell.org> #13810: Gold linker fails ---------------------------------+---------------------------------------- Reporter: ksaric | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.2.1 Component: Compiler | Version: 8.0.1 Resolution: wontfix | Keywords: linker Operating System: Linux | Architecture: Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | ---------------------------------+---------------------------------------- Comment (by Ben Gamari ): In [changeset:"625143f473b58d770d2515b91c2566b52d35a4c3/ghc" 625143f4/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="625143f473b58d770d2515b91c2566b52d35a4c3" configure: Coerce gcc to use $LD instead of system default The configure script will now try to coerce gcc to use the linker pointed to by $LD instead of the system default (typically bfd ld). Moreover, we now check for `ld.gold` and `ld.lld` before trying `ld`. The previous behavior can be reverted to by using the new --disable-ld-override flag. On my machine gold seems to trigger an apparent infelicity in constructor behavior, causing T5435_asm to fail. I've opened #13883 to record this issue and have accepted the questionable constructor ordering for the time being. Test Plan: Validate with `config_args='--enable-ld-override'` Reviewers: austin, hvr, simonmar Subscribers: duog, nh2, rwbarton, thomie, erikd, snowleopard GHC Trac Issues: #13541, #13810, #13883 Differential Revision: https://phabricator.haskell.org/D3449 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 30 00:18:22 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 30 Jun 2017 00:18:22 -0000 Subject: [GHC] #13875: ApplicativeDo desugaring is lazier than standard desugaring In-Reply-To: <045.2eda858359df0999208d04da5f95a1da@haskell.org> References: <045.2eda858359df0999208d04da5f95a1da@haskell.org> Message-ID: <060.299906b857431c935d09bebe73792d6d@haskell.org> #13875: ApplicativeDo desugaring is lazier than standard desugaring -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: simonmar Type: bug | Status: patch Priority: high | Milestone: 8.2.1 Component: Compiler | Version: 8.3 Resolution: | Keywords: ApplicativeDo Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Other | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3681 Wiki Page: | -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"1ef4156e45dcb258f6ef05cfb909547b8e3beb0f/ghc" 1ef4156/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="1ef4156e45dcb258f6ef05cfb909547b8e3beb0f" Prevent ApplicativeDo from applying to strict pattern matches (#13875) Test Plan: * New unit tests * validate Reviewers: dfeuer, simonpj, niteria, bgamari, austin, erikd Reviewed By: dfeuer Subscribers: rwbarton, thomie GHC Trac Issues: #13875 Differential Revision: https://phabricator.haskell.org/D3681 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 30 00:18:21 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 30 Jun 2017 00:18:21 -0000 Subject: [GHC] #13541: Make it easier to use the gold linker In-Reply-To: <046.0b1321a637ed3292c60514e6510d2c09@haskell.org> References: <046.0b1321a637ed3292c60514e6510d2c09@haskell.org> Message-ID: <061.5f6a8fe3e1b5fba36b5a7db9e43ee8b5@haskell.org> #13541: Make it easier to use the gold linker -------------------------------------+------------------------------------- Reporter: bgamari | Owner: bgamari Type: feature request | Status: patch Priority: highest | Milestone: 8.2.1 Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #13810, #13739 | Differential Rev(s): Phab:D3449 Wiki Page: | -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"625143f473b58d770d2515b91c2566b52d35a4c3/ghc" 625143f4/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="625143f473b58d770d2515b91c2566b52d35a4c3" configure: Coerce gcc to use $LD instead of system default The configure script will now try to coerce gcc to use the linker pointed to by $LD instead of the system default (typically bfd ld). Moreover, we now check for `ld.gold` and `ld.lld` before trying `ld`. The previous behavior can be reverted to by using the new --disable-ld-override flag. On my machine gold seems to trigger an apparent infelicity in constructor behavior, causing T5435_asm to fail. I've opened #13883 to record this issue and have accepted the questionable constructor ordering for the time being. Test Plan: Validate with `config_args='--enable-ld-override'` Reviewers: austin, hvr, simonmar Subscribers: duog, nh2, rwbarton, thomie, erikd, snowleopard GHC Trac Issues: #13541, #13810, #13883 Differential Revision: https://phabricator.haskell.org/D3449 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 30 00:24:58 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 30 Jun 2017 00:24:58 -0000 Subject: [GHC] #8281: The impossible happened: primRepToFFIType In-Reply-To: <044.47e20917996e473150de04c1ce1afc0b@haskell.org> References: <044.47e20917996e473150de04c1ce1afc0b@haskell.org> Message-ID: <059.7447f63bd7c131b5d2ad1a2af0894b2a@haskell.org> #8281: The impossible happened: primRepToFFIType -------------------------------------+------------------------------------- Reporter: tibbe | Owner: (none) Type: bug | Status: new Priority: high | Milestone: 8.4.1 Component: Compiler | Version: 7.6.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3619 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: patch => new Comment: The GHCi FFI safety issue has been resolved (for 8.4) with comment:29, but I believe the original issue remains unsolved. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 30 00:25:49 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 30 Jun 2017 00:25:49 -0000 Subject: [GHC] #13747: Can't use 'instance' keyword in associated type family instance In-Reply-To: <042.cfa21cd9140248a25075b778770d0326@haskell.org> References: <042.cfa21cd9140248a25075b778770d0326@haskell.org> Message-ID: <057.97d8ac5f210ec264d5f4e8d441c98388@haskell.org> #13747: Can't use 'instance' keyword in associated type family instance -------------------------------------+------------------------------------- Reporter: nh2 | Owner: erdeszt Type: bug | Status: closed Priority: normal | Milestone: 8.4.1 Component: Compiler | Version: 8.0.2 Resolution: fixed | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple error/warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3673 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => closed * resolution: => fixed * milestone: => 8.4.1 Comment: Thanks erdeszt! -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 30 00:26:13 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 30 Jun 2017 00:26:13 -0000 Subject: [GHC] #13541: Make it easier to use the gold linker In-Reply-To: <046.0b1321a637ed3292c60514e6510d2c09@haskell.org> References: <046.0b1321a637ed3292c60514e6510d2c09@haskell.org> Message-ID: <061.d47cb14f4a9c3a60f0c271ebe650c052@haskell.org> #13541: Make it easier to use the gold linker -------------------------------------+------------------------------------- Reporter: bgamari | Owner: bgamari Type: feature request | Status: merge Priority: highest | Milestone: 8.2.1 Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #13810, #13739 | Differential Rev(s): Phab:D3449 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: patch => merge -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 30 00:26:30 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 30 Jun 2017 00:26:30 -0000 Subject: [GHC] #13875: ApplicativeDo desugaring is lazier than standard desugaring In-Reply-To: <045.2eda858359df0999208d04da5f95a1da@haskell.org> References: <045.2eda858359df0999208d04da5f95a1da@haskell.org> Message-ID: <060.225d0d83e0e86e311438bb4029a27cfd@haskell.org> #13875: ApplicativeDo desugaring is lazier than standard desugaring -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: simonmar Type: bug | Status: merge Priority: high | Milestone: 8.2.1 Component: Compiler | Version: 8.3 Resolution: | Keywords: ApplicativeDo Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Other | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3681 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: patch => merge -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 30 00:35:55 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 30 Jun 2017 00:35:55 -0000 Subject: [GHC] #13900: Core lint in BuildFlavour=perf-llvm In-Reply-To: <046.659e0b338788e413a5940905a0f91074@haskell.org> References: <046.659e0b338788e413a5940905a0f91074@haskell.org> Message-ID: <061.d29b96d1426eb9f1d4b7fea310695943@haskell.org> #13900: Core lint in BuildFlavour=perf-llvm -------------------------------------+------------------------------------- Reporter: bgamari | Owner: (none) Type: bug | Status: new Priority: high | Milestone: 8.4.1 Component: Compiler | Version: 8.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Description changed by bgamari: @@ -2,1 +2,2 @@ - c9977385dca9536f18374242f713b1048a38dec5 with `BuildFlavour=perf-llvm`, + c9977385dca9536f18374242f713b1048a38dec5 with `BuildFlavour=perf-llvm` and + `GhcStage2HcOpts += -dcore-lint -dcmm-lint`, New description: I found the following Core lint failure when compiling c9977385dca9536f18374242f713b1048a38dec5 with `BuildFlavour=perf-llvm` and `GhcStage2HcOpts += -dcore-lint -dcmm-lint`, {{{ "inplace/bin/ghc-stage1" -hisuf dyn_hi -osuf dyn_o -hcsuf dyn_hc -fPIC -dynamic -O -H64m -fllvm -Wall -hide-all-packages -i -ighc/. -ighc/stage2/build -Ighc/stage2/build -ighc/stage2/build/ghc/autogen -Ighc/stage2/build/ghc/autogen -optP-DGHCI -optP-include -optPghc/stage2/build/ghc/autogen/cabal_macros.h -package-id base-4.10.0.0 -package-id array-0.5.1.2 -package-id bytestring-0.10.8.2 -package-id directory-1.3.0.2 -package-id process-1.6.0.0 -package-id filepath-1.4.1.2 -package-id ghc-boot-8.3 -package-id ghc-8.3 -package-id unix-2.7.2.2 -package-id containers-0.5.10.2 -package-id deepseq-1.4.3.0 -package-id ghci-8.3 -package-id haskeline-0.7.4.0 -package-id time-1.8.0.1 -package- id transformers-0.5.2.0 -Wall -fno-warn-name-shadowing -XHaskell2010 -O2 -dcore-lint -dcmm-lint -no-hs-main -threaded -no-user-package-db -rtsopts -Wnoncanonical-monad-instances -odir ghc/stage2/build -hidir ghc/stage2/build -stubdir ghc/stage2/build -c ghc/./GHCi/UI/Tags.hs -o ghc/stage2/build/GHCi/UI/Tags.dyn_o *** Core Lint errors : in result of Simplifier *** : warning: [RHS of $wgo_XtpE :: [Name] -> Session -> State# RealWorld -> (# State# RealWorld, [[TagInfo]] #)] Rule "SC:$wgo0": lhs type: (# State# RealWorld, [[TagInfo]] #) rhs type: (# State# RealWorld, [Maybe TyThing] #) *** Offending Program *** (see attached) }}} -- -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 30 00:56:19 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 30 Jun 2017 00:56:19 -0000 Subject: [GHC] #8033: add AVX register support to llvm calling convention In-Reply-To: <045.7dc8866bbad0b343f7d0cca58aa9a9b3@haskell.org> References: <045.7dc8866bbad0b343f7d0cca58aa9a9b3@haskell.org> Message-ID: <060.b021a69c80766b95358403980b3aec9a@haskell.org> #8033: add AVX register support to llvm calling convention -------------------------------------+------------------------------------- Reporter: carter | Owner: (none) Type: task | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.7 Resolution: | Keywords: SIMD Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): See https://reviews.llvm.org/D34854. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 30 01:24:34 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 30 Jun 2017 01:24:34 -0000 Subject: [GHC] #13434: hs_try_putmvar003 is timing out / segfaulting In-Reply-To: <045.a8ba4ff49dee16c0019e5f315e9937ac@haskell.org> References: <045.a8ba4ff49dee16c0019e5f315e9937ac@haskell.org> Message-ID: <060.8ea61acf85eca7842acf48d1ab1503d4@haskell.org> #13434: hs_try_putmvar003 is timing out / segfaulting -------------------------------------+------------------------------------- Reporter: ezyang | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Runtime System | Version: 8.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Runtime crash | Test Case: Blocked By: | Blocking: 13722 Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): jared-w seems to be seeing this reproducibly on his machine. We haven't yet determined what it is about his setup that makes this so, but he uses Arch Linux machine on a dual-core machine. `+RTS -Ds` says the following before hanging, {{{ ... 7ff838ff9700: cap 0: schedule() 7ff838ff9700: giving up capability 0 7ff838ff9700: passing capability 0 to worker 0x7ff8397fa700 7ff8397fa700: resuming capability 0 7ff8397fa700: cap 0: running thread 515 (ThreadRunGHC) 7ff8397fa700: cap 0: thread 515 stopped (blocked on an MVar) thread 515 @ 0x4200369d98 is blocked on an MVar @ 0x420003c798 (TSO_DIRTY) 7ff8397fa700: giving up capability 0 7ff8397fa700: freeing capability 0 7ff894ff9700: cap 0: waking up thread 515 on cap 0 7ff894ff9700: passing capability 0 to worker 0x7ff8397fa700 7ff8397fa700: woken up on capability 0 7ff8397fa700: resuming capability 0 7ff8397fa700: cap 0: running thread 515 (ThreadRunGHC) 7ff8397fa700: cap 0: waking up thread 117 on cap 0 7ff8397fa700: cap 0: thread 515 stopped (finished) 7ff8397fa700: cap 0: running thread 117 (ThreadRunGHC) 7ff8397fa700: cap 0: thread 117 stopped (suspended while making a foreign call) 7ff8397fa700: freeing capability 0 7ff8b718b700: returning; I want capability 0 7ff8b718b700: resuming capability 0 7ff8b718b700: cap 0: running thread 3 (ThreadRunGHC) 7ff8b718b700: cap 0: thread 3 stopped (yielding) 7ff8b718b700: cap 0: running thread 3 (ThreadRunGHC) 7ff8b718b700: cap 0: thread 3 stopped (suspended while making a foreign call) 7ff8b718b700: passing capability 0 to worker 0x7ff838ff9700 7ff838ff9700: woken up on capability 0 7ff838ff9700: resuming capability 0 7ff838ff9700: deadlocked, forcing major GC... 7ff838ff9700: cap 0: requesting parallel GC 7ff838ff9700: 0 idle caps all threads: threads on capability 0: other threads: thread 117 @ 0x4200368920 is blocked on an external call (TSO_DIRTY) thread 116 @ 0x42002c6b58 is blocked on an external call (TSO_DIRTY) thread 115 @ 0x42003f0d88 is blocked on an external call thread 114 @ 0x42003fc858 is blocked on an external call (TSO_DIRTY) thread 24 @ 0x4200361e28 is blocked on an external call (TSO_DIRTY) thread 23 @ 0x42003ebdb0 is blocked on an external call (TSO_DIRTY) thread 22 @ 0x42003d5858 is blocked on an external call (TSO_DIRTY) thread 21 @ 0x42003d1400 is blocked on an external call (TSO_DIRTY) thread 20 @ 0x42003e1400 is blocked on an external call (TSO_DIRTY) thread 19 @ 0x42003d2858 is blocked on an external call thread 18 @ 0x42003a40a0 is blocked on an external call thread 17 @ 0x4200397a88 is blocked on an external call (TSO_DIRTY) thread 16 @ 0x42003bcec8 is blocked on an external call (TSO_DIRTY) thread 15 @ 0x4200393f28 is blocked on an external call (TSO_DIRTY) thread 14 @ 0x420039d9e8 is blocked on an external call (TSO_DIRTY) thread 5 @ 0x42003744c8 is blocked on an external call (TSO_DIRTY) thread 4 @ 0x420036e358 is blocked on an MVar @ 0x420036da10 thread 3 @ 0x42002ba0f0 ["TimerManager"] is blocked on an external call (TSO_DIRTY) thread 2 @ 0x42002ba168 ["IOManager on cap 0"] is blocked on an external call 7ff838ff9700: cap 0: starting GC 7ff838ff9700: cap 0: GC working 7ff838ff9700: cap 0: GC idle 7ff838ff9700: cap 0: GC done 7ff838ff9700: cap 0: GC idle 7ff838ff9700: cap 0: GC done 7ff838ff9700: cap 0: GC idle 7ff838ff9700: cap 0: GC done 7ff838ff9700: cap 0: all caps stopped for GC 7ff838ff9700: cap 0: finished GC 7ff838ff9700: giving up capability 0 7ff838ff9700: freeing capability 0 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 30 02:26:45 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 30 Jun 2017 02:26:45 -0000 Subject: [GHC] #13541: Make it easier to use the gold linker In-Reply-To: <046.0b1321a637ed3292c60514e6510d2c09@haskell.org> References: <046.0b1321a637ed3292c60514e6510d2c09@haskell.org> Message-ID: <061.b652d544c81f7f473a15f864ea3844aa@haskell.org> #13541: Make it easier to use the gold linker -------------------------------------+------------------------------------- Reporter: bgamari | Owner: bgamari Type: feature request | Status: closed Priority: highest | Milestone: 8.2.1 Component: Compiler | Version: 8.0.1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #13810, #13739 | Differential Rev(s): Phab:D3449 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: merge => closed * resolution: => fixed Comment: Merged to `ghc-8.2` as 2785ef0e31a123400da950ffafebe6cb1ce3f4eb. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 30 02:27:10 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 30 Jun 2017 02:27:10 -0000 Subject: [GHC] #13875: ApplicativeDo desugaring is lazier than standard desugaring In-Reply-To: <045.2eda858359df0999208d04da5f95a1da@haskell.org> References: <045.2eda858359df0999208d04da5f95a1da@haskell.org> Message-ID: <060.6421443eccba730dd812afe411bb5a6c@haskell.org> #13875: ApplicativeDo desugaring is lazier than standard desugaring -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: simonmar Type: bug | Status: closed Priority: high | Milestone: 8.2.1 Component: Compiler | Version: 8.3 Resolution: fixed | Keywords: ApplicativeDo Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Other | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3681 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: merge => closed * resolution: => fixed Comment: Merged to `ghc-8.2` with 97aa533fd8bcbd8e42b3358e8a07423ad2a2d01f. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 30 02:31:13 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 30 Jun 2017 02:31:13 -0000 Subject: [GHC] #13222: Update formalism for join points In-Reply-To: <049.b34747a00c615a5f34c9610329937813@haskell.org> References: <049.b34747a00c615a5f34c9610329937813@haskell.org> Message-ID: <064.e98c16f6e12327c9f7107b3b526e9730@haskell.org> #13222: Update formalism for join points -------------------------------------+------------------------------------- Reporter: lukemaurer | Owner: lukemaurer Type: task | Status: patch Priority: normal | Milestone: 8.2.1 Component: Compiler | Version: 8.1 Resolution: | Keywords: JoinPoints Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Other | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3296 Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): This is waiting on me to rework our handling of the core lint formalism PDF. Currently it's checked in to the repository, meaning that around 300kB is added to the repo on every change. Being a generated artifact, it really doesn't belong under version control but it requires non-trivial tools to generate, so we need to place a copy somewhere before removing it. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 30 02:31:26 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 30 Jun 2017 02:31:26 -0000 Subject: [GHC] #13222: Update formalism for join points In-Reply-To: <049.b34747a00c615a5f34c9610329937813@haskell.org> References: <049.b34747a00c615a5f34c9610329937813@haskell.org> Message-ID: <064.25c38d941dac12cadf1ababc29b5e855@haskell.org> #13222: Update formalism for join points -------------------------------------+------------------------------------- Reporter: lukemaurer | Owner: lukemaurer Type: task | Status: patch Priority: normal | Milestone: 8.2.2 Component: Compiler | Version: 8.1 Resolution: | Keywords: JoinPoints Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Other | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3296 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * milestone: 8.2.1 => 8.2.2 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 30 04:41:45 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 30 Jun 2017 04:41:45 -0000 Subject: [GHC] #13886: GHC panic when using GHC plugins In-Reply-To: <048.4e65bf02b6c4ff69cd509bbe731fe7ea@haskell.org> References: <048.4e65bf02b6c4ff69cd509bbe731fe7ea@haskell.org> Message-ID: <063.26a9819528d8771e190f8301cf9c971c@haskell.org> #13886: GHC panic when using GHC plugins -------------------------------------+------------------------------------- Reporter: Darwin226 | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 8.0.2 Resolution: duplicate | Keywords: Operating System: Windows | Architecture: x86_64 Type of failure: Compile-time | (amd64) crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: #10301 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * status: new => closed * resolution: => duplicate * related: => #10301 Comment: I can confirm that a simple `dump-core` example works without problems on GHC 8.2.1-rc2, so I'll close this as a duplicate. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 30 06:45:29 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 30 Jun 2017 06:45:29 -0000 Subject: [GHC] #13901: Lift the "Illegal polymorphic type" restriction on type families Message-ID: <050.9aec2c0b0f1e57bc955033f5ea3e1669@haskell.org> #13901: Lift the "Illegal polymorphic type" restriction on type families -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: feature | Status: new request | Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 (Type checker) | Keywords: TypeFamilies | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: #11962 Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- Currently, I can do this: {{{#!hs type Foo = forall a. Maybe a }}} But if I try to refactor this to an equivalent type family: {{{#!hs type family Foo where Foo = forall a. Maybe a }}} Then GHC complains: {{{ • Illegal polymorphic type: forall a. Maybe a • In the equations for closed type family ‘Foo’ In the type family declaration for ‘Foo’ }}} We should lift this restriction. This would be necessary, for instance, to implement #11962. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 30 06:47:06 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 30 Jun 2017 06:47:06 -0000 Subject: [GHC] #11962: Support induction recursion In-Reply-To: <047.045273ef2ac55a0385e215af795b4757@haskell.org> References: <047.045273ef2ac55a0385e215af795b4757@haskell.org> Message-ID: <062.756271bf8c8b6c3376593fbe7a2fbda1@haskell.org> #11962: Support induction recursion -------------------------------------+------------------------------------- Reporter: goldfire | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.1 Resolution: | Keywords: TypeInType Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #13901 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * related: => #13901 Comment: Replying to [ticket:11962 goldfire]: > (I'm cheating a bit here, because for unrelated reasons, we can't return a `forall` on the right-hand side of a type family. But that's not the issue at hand.) I'm tracking this issue separately at #13901, since I would find that useful in its own right. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 30 07:45:15 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 30 Jun 2017 07:45:15 -0000 Subject: [GHC] #13902: Misleading function arity mismatch error with TypeApplications Message-ID: <050.514c9079ae10e5fa5ab2326b10b1fa2b@haskell.org> #13902: Misleading function arity mismatch error with TypeApplications -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 (Type checker) | Keywords: | Operating System: Unknown/Multiple TypeApplications | Architecture: | Type of failure: Poor/confusing Unknown/Multiple | error message Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- {{{#!hs {-# LANGUAGE TypeApplications #-} f :: a -> a f x = x g :: Int g = f @Int 42 5 }}} {{{ GHCi, version 8.3.20170614: http://www.haskell.org/ghc/ :? for help Loaded GHCi configuration from /home/rgscott/.ghci [1 of 1] Compiling Main ( Bug.hs, interpreted ) Bug.hs:7:5: error: • Couldn't match expected type ‘Integer -> Int’ with actual type ‘Int’ • The function ‘f’ is applied to three arguments, but its type ‘Int -> Int’ has only one In the expression: f @Int 42 5 In an equation for ‘g’: g = f @Int 42 5 | 7 | g = f @Int 42 5 | ^^^^^^^^^^^ }}} That error message is quite confusing to read, since it reports that: * `f` is applied to three arguments, which //includes// a visible type application * `f` only has one argument, which //excludes// the visible type application We ought to be able to do better. My suggestion would be to report this instead: {{{ • The function ‘f @Int’ is applied to two arguments, but its type ‘Int -> Int’ has only one In the expression: f @Int 42 5 In an equation for ‘g’: g = f @Int 42 5 }}} Although I'm sure there are other ways the same information could be conveyed (e.g., `The function ‘f’ is applied to two value arguments`). -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 30 07:56:22 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 30 Jun 2017 07:56:22 -0000 Subject: [GHC] #11409: Cannot instantiate literals using TypeApplications In-Reply-To: <048.6352883c4ebf7b6ed5ee4d78320dfea2@haskell.org> References: <048.6352883c4ebf7b6ed5ee4d78320dfea2@haskell.org> Message-ID: <063.afbd3dfdcb7e6126380c1299e24fa181@haskell.org> #11409: Cannot instantiate literals using TypeApplications -------------------------------------+------------------------------------- Reporter: Feuerbach | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: 8.4.1 Component: Compiler | Version: 8.0.1-rc1 Resolution: | Keywords: | TypeApplications Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #11352 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by adamgundry): Rather than defining `integerLit`, perhaps we should just treat a type application to an overloaded literal specially, and say that `5 @Int` desugars to `fromInteger @Int 5`? This would work with `RebindableSyntax` just fine. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 30 08:51:51 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 30 Jun 2017 08:51:51 -0000 Subject: [GHC] #11721: GADT-syntax data constructors don't work well with TypeApplications In-Reply-To: <047.d3cda57aa918919c3cdf02eb21c0a581@haskell.org> References: <047.d3cda57aa918919c3cdf02eb21c0a581@haskell.org> Message-ID: <062.50fb25fdd6ebc5b8b88ff45cc1d896db@haskell.org> #11721: GADT-syntax data constructors don't work well with TypeApplications -------------------------------------+------------------------------------- Reporter: goldfire | Owner: RyanGlScott Type: bug | Status: new Priority: normal | Milestone: 8.4.1 Component: Compiler | Version: 8.1 Resolution: | Keywords: | TypeApplications Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #13848 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): See discussion in #13848 (only closed because duplicate) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 30 09:32:47 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 30 Jun 2017 09:32:47 -0000 Subject: [GHC] #13901: Lift the "Illegal polymorphic type" restriction on type families In-Reply-To: <050.9aec2c0b0f1e57bc955033f5ea3e1669@haskell.org> References: <050.9aec2c0b0f1e57bc955033f5ea3e1669@haskell.org> Message-ID: <065.431950c0dc7d0e409ff142a2ee5c7a3b@haskell.org> #13901: Lift the "Illegal polymorphic type" restriction on type families -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.1 checker) | Resolution: | Keywords: TypeFamilies Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #11962 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by Iceland_jack): * cc: Iceland_jack (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 30 09:38:02 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 30 Jun 2017 09:38:02 -0000 Subject: [GHC] #13884: To an automatic compilation of file-header LANGUAGE pragmas in GHC. In-Reply-To: <044.5438e0b55f2f96ccdf324b161ad363cb@haskell.org> References: <044.5438e0b55f2f96ccdf324b161ad363cb@haskell.org> Message-ID: <059.ac17b7a9b8371b25626e83f5e6379c11@haskell.org> #13884: To an automatic compilation of file-header LANGUAGE pragmas in GHC. -------------------------------------+------------------------------------- Reporter: vanto | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Other | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by vanto): * status: closed => new * resolution: wontfix => Comment: >> However, I don't believe the compiler is the right place for this sort of logic. It is established that you do not know the Ada language compiler.\\ I think your answer is an arbitrary answer. Besides you are not the only one to have this kind of answer in the Committee. Often your responses that do not relate to a bug are arbitrary and seems to be controlled by anything other than rational reason.\\ If you close this ticket, you do not correct anything and you forget. I reopen it even if you do not follow it, someone else later will take it into account for a more complete exploitation.\\ You are forty people on the Committee, your opinion alone does not make law to close this ticket. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 30 09:44:33 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 30 Jun 2017 09:44:33 -0000 Subject: [GHC] #13893: Improved Help for Control.Concurrent and Control.Exception when "variable not in scope" In-Reply-To: <044.50a1c8e97ad1d72587a33a02855fe4cb@haskell.org> References: <044.50a1c8e97ad1d72587a33a02855fe4cb@haskell.org> Message-ID: <059.f637eaf2b1c175ccb260da8f32308210@haskell.org> #13893: Improved Help for Control.Concurrent and Control.Exception when "variable not in scope" -------------------------------------+------------------------------------- Reporter: vanto | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Poor/confusing | Unknown/Multiple error message | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by vanto): * status: closed => new * resolution: wontfix => Comment: >>don't believe the compiler is the right place to solve it\\ It is established that you do not know the Ada language compiler.\\ If you close this ticket, you do not correct anything and you forget. I reopen it even if you do not follow it, someone else later will take it into account for a more complete exploitation. I think your answer is an arbitrary answer. Often the answers of some of you that do not relate to a bug are arbitrary and seems to be controlled by anything other than rational reason. You are forty people on the Committee, your opinion alone does not make law to close this ticket. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 30 09:45:06 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 30 Jun 2017 09:45:06 -0000 Subject: [GHC] #4210: LLVM: Dynamic Library Support In-Reply-To: <045.9da2e8588befc1a62c55be781a6ff87b@haskell.org> References: <045.9da2e8588befc1a62c55be781a6ff87b@haskell.org> Message-ID: <060.9d949f981dc998f76d53dc15be0502c2@haskell.org> #4210: LLVM: Dynamic Library Support -------------------------------------+------------------------------------- Reporter: dterei | Owner: dterei Type: feature request | Status: closed Priority: low | Milestone: 7.6.2 Component: Compiler (LLVM) | Version: 6.13 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Runtime crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by slyfox): Ben, there is a proposed patch upstream. Do you have the hardware to try it on? https://sourceware.org/bugzilla/show_bug.cgi?id=16177#c2 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 30 09:46:35 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 30 Jun 2017 09:46:35 -0000 Subject: [GHC] #13747: Can't use 'instance' keyword in associated type family instance In-Reply-To: <042.cfa21cd9140248a25075b778770d0326@haskell.org> References: <042.cfa21cd9140248a25075b778770d0326@haskell.org> Message-ID: <057.0e892ecadda0aa27e11fa6c01816b076@haskell.org> #13747: Can't use 'instance' keyword in associated type family instance -------------------------------------+------------------------------------- Reporter: nh2 | Owner: erdeszt Type: bug | Status: closed Priority: normal | Milestone: 8.4.1 Component: Compiler | Version: 8.0.2 Resolution: fixed | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple error/warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3673 Wiki Page: | -------------------------------------+------------------------------------- Comment (by nh2): Indeed, thanks a lot! Come to Zurich, show me this ticket and I owe you a beverage of your choice. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 30 10:02:57 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 30 Jun 2017 10:02:57 -0000 Subject: [GHC] #11409: Cannot instantiate literals using TypeApplications In-Reply-To: <048.6352883c4ebf7b6ed5ee4d78320dfea2@haskell.org> References: <048.6352883c4ebf7b6ed5ee4d78320dfea2@haskell.org> Message-ID: <063.5f120d02deb1362f9bcbc6c8825a49c0@haskell.org> #11409: Cannot instantiate literals using TypeApplications -------------------------------------+------------------------------------- Reporter: Feuerbach | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: 8.4.1 Component: Compiler | Version: 8.0.1-rc1 Resolution: | Keywords: | TypeApplications Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #11352 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Iceland_jack): That sounds good Adam -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 30 10:10:19 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 30 Jun 2017 10:10:19 -0000 Subject: [GHC] #13902: Misleading function arity mismatch error with TypeApplications In-Reply-To: <050.514c9079ae10e5fa5ab2326b10b1fa2b@haskell.org> References: <050.514c9079ae10e5fa5ab2326b10b1fa2b@haskell.org> Message-ID: <065.031bb45ba6f8c6169413324b82be5c23@haskell.org> #13902: Misleading function arity mismatch error with TypeApplications -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.1 checker) | Keywords: Resolution: | TypeApplications Operating System: Unknown/Multiple | Architecture: Type of failure: Poor/confusing | Unknown/Multiple error message | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Iceland_jack): I like treating the function and visible type application as a whole. The type of `f @Int` is `Int -> Int` and takes a single argument but that is not the type of `f` -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 30 10:30:35 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 30 Jun 2017 10:30:35 -0000 Subject: [GHC] #13903: KQueue evtmgr backend fails to register for write events Message-ID: <048.b40d50b7e059c68fc52d5bbd492f52b4@haskell.org> #13903: KQueue evtmgr backend fails to register for write events -------------------------------------+------------------------------------- Reporter: waldheinz | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Runtime | Version: 8.0.2 System | Keywords: | Operating System: FreeBSD Architecture: | Type of failure: Incorrect result Unknown/Multiple | at runtime Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- The root of the problem is that the `GHC.Event.KQueue.toFilter` function has type `GHC.Event.Internal.Event -> Filter` with GHC's `Event` being a bitmask which can represent read events, write events or a combination of those. It happens that the event manager requests it's backend to be notified about read ''and'' write events on some fd, and because the kqueue `EVFILT_*`s are ''not'' bitmasks, the above function cannot capture this, silently dropping the desire to be notified about write events. The following program triggers the problematic behaviour: {{{ import Control.Concurrent ( forkIO, killThread ) import Control.Exception ( finally ) import Control.Monad.Trans.Resource ( runResourceT ) import Control.Monad.IO.Class ( liftIO ) import qualified Data.ByteString as BS import Data.Conduit ( ($$), ($=) ) import qualified Data.Conduit.Binary as CB import qualified Data.Conduit.List as CL import qualified Data.Conduit.Network as CN import Data.IORef ( newIORef, modifyIORef', readIORef) main :: IO () main = CN.runTCPClient (CN.clientSettings 5555 "192.168.2.11") client where logMsg cnt = CL.mapM $ \bs -> liftIO $ do modifyIORef' cnt (+ 1) readIORef cnt >>= \x -> putStrLn $ "msg #" ++ show x ++ " of size: " ++ show (BS.length bs) return bs client ad = do reader <- forkIO (runResourceT $ CN.appSource ad $$ CL.mapM_ ( \bs -> (liftIO . putStrLn) $ "read " ++ show (BS.length bs) ++ " bytes")) cnt <- newIORef ( 0 :: Int ) let runPipe = runResourceT $ CB.sourceFile "cool-linux-distro.iso" $$ logMsg cnt $= CN.appSink ad runPipe `finally` (killThread reader) }}} Having a `nc -l -p 5555 > /dev/null` running on another machine is sufficient to sink the data. Assuming that we can read `bigfile.iso` faster than we can send out over the socket, the `send` syscall will at some point give an `EAGAIN` as can be seen in the `truss` output: {{{ write(1,"msg #20 of size: 32752\n",23) = 23 (0x17) sendto(12,"\f\2409\0\M^RA\^T\M-&A\M-'\M-d8"...,32752,0x0,NULL,0x0) = 32752 (0x7ff0) read(13,"\M^?\0'\\\M-B\M-:+\^]D\M-0\M-="...,32752) = 32752 (0x7ff0) poll({ 1/POLLOUT },1,0) = 1 (0x1) msg #21 of size: 32752 write(1,"msg #21 of size: 32752\n",23) = 23 (0x17) sendto(12,"\M^?\0'\\\M-B\M-:+\^]D\M-0\M-="...,32752,0x0,NULL,0x0) = 19204 (0x4b04) sendto(12,"\M-j$2\M^BH\M-#-\^A\M-E\^O\M^Y\a"...,13548,0x0,NULL,0x0) ERR#35 'Resource temporarily unavailable' SIGNAL 26 (SIGVTALRM) sigprocmask(SIG_SETMASK,{ SIGVTALRM },0x0) = 0 (0x0) sigreturn(0x7fffffff9c60) ERR#35 'Resource temporarily unavailable' kevent(3,{ 12,EVFILT_READ,EV_ADD|EV_ONESHOT,0x0,0x0,0x0 },1,0x0,0,{ 0.000000000 }) = 0 (0x0) _umtx_op(0x800c71ed0,UMTX_OP_WAIT_UINT_PRIVATE,0x0,0x0,0x0) ERR#4 'Interrupted system call' SIGNAL 26 (SIGVTALRM) sigprocmask(SIG_SETMASK,{ SIGVTALRM },0x0) = 0 (0x0) sigreturn(0x7fffffffdc00) ERR#4 'Interrupted system call' _umtx_op(0x800c71ed0,UMTX_OP_WAIT_UINT_PRIVATE,0x0,0x0,0x0) ERR#4 'Interrupted system call' SIGNAL 26 (SIGVTALRM) }}} Not the `sendto` call on fd 12 resulting in `ERR#35`, soon followed by an `kevent` call for that same fd and only `EVFILT_READ` set. This makes little sense as it was an attempt to ''write'' that just failed. This is caused by `toFilter` giving precedence to `read` events, dropping the write event. Not starting the `reader` thread prevents bad things from happening as then the `write` events are properly passed thru to kqueue. I have an initial version of a patch fixing this. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 30 10:39:52 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 30 Jun 2017 10:39:52 -0000 Subject: [GHC] #13767: GHCi trips -DS checks at rts/sm/Sanity.c, line 210 In-Reply-To: <046.e0bf705a7b0da22195c9831465099e74@haskell.org> References: <046.e0bf705a7b0da22195c9831465099e74@haskell.org> Message-ID: <061.5c529473aa67d11c83857a08ba1b23d1@haskell.org> #13767: GHCi trips -DS checks at rts/sm/Sanity.c, line 210 -------------------------------------+------------------------------------- Reporter: niteria | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Runtime System | Version: 8.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3680 Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonmar): * differential: => Phab:D3680 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 30 10:52:59 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 30 Jun 2017 10:52:59 -0000 Subject: [GHC] #13903: KQueue evtmgr backend fails to register for write events In-Reply-To: <048.b40d50b7e059c68fc52d5bbd492f52b4@haskell.org> References: <048.b40d50b7e059c68fc52d5bbd492f52b4@haskell.org> Message-ID: <063.69f6c0c2f7d58a3fbb7a5a55418d5dad@haskell.org> #13903: KQueue evtmgr backend fails to register for write events -------------------------------------+------------------------------------- Reporter: waldheinz | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Runtime System | Version: 8.0.2 Resolution: | Keywords: Operating System: FreeBSD | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by waldheinz): I'm unable to create attachments here, keep getting "IndexError: pop from empty list" errors from Trac. So please have a look here meanwhile: https://github.com/waldheinz/ghc/commit/921a39eb2cd0d589696657a5857d45cf00b895aa -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 30 12:50:28 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 30 Jun 2017 12:50:28 -0000 Subject: [GHC] #13902: Misleading function arity mismatch error with TypeApplications In-Reply-To: <050.514c9079ae10e5fa5ab2326b10b1fa2b@haskell.org> References: <050.514c9079ae10e5fa5ab2326b10b1fa2b@haskell.org> Message-ID: <065.b4410badac46f02b0e6d4c3ace108886@haskell.org> #13902: Misleading function arity mismatch error with TypeApplications -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.1 checker) | Keywords: Resolution: | TypeApplications Operating System: Unknown/Multiple | Architecture: Type of failure: Poor/confusing | Unknown/Multiple error message | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by vanto): >>We ought to be able to do better.\\ Yes and it's good to share ideas.\\ I'd like to make a suggestion. It is not worth writing {{{ In the expression: f @Int 42 5 In an equation for ‘g’: g = f @Int 42 5 }}} Since the compiler already indicates the place that has the expression and equation.\\ {{{ | 7 | g = f @Int 42 5 | ^^^^^^^^^^^ }}} Both sentences make redundancy and does not serve better to explain. Too much explanation is detrimental to the explanation. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 30 13:26:33 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 30 Jun 2017 13:26:33 -0000 Subject: [GHC] #13903: KQueue evtmgr backend fails to register for write events In-Reply-To: <048.b40d50b7e059c68fc52d5bbd492f52b4@haskell.org> References: <048.b40d50b7e059c68fc52d5bbd492f52b4@haskell.org> Message-ID: <063.2c58f19aa1ff32627d6edf6ab3cce39a@haskell.org> #13903: KQueue evtmgr backend fails to register for write events -------------------------------------+------------------------------------- Reporter: waldheinz | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Runtime System | Version: 8.0.2 Resolution: | Keywords: Operating System: FreeBSD | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by waldheinz): I think I managed to get a proper version of the patch on Phabricator: > https://phabricator.haskell.org/D3692 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 30 13:56:02 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 30 Jun 2017 13:56:02 -0000 Subject: [GHC] #13904: LLVM does not need to trash callee-saved registers. Message-ID: <044.9fbf455960cc2fbed77cfe6c815566aa@haskell.org> #13904: LLVM does not need to trash callee-saved registers. -------------------------------------+------------------------------------- Reporter: kavon | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Keywords: llvm, codegen | Operating System: Unknown/Multiple Architecture: | Type of failure: Compile-time Unknown/Multiple | performance bug Test Case: | Blocked By: Blocking: | Related Tickets: #4992 Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- **Summary**: This ticket is a simplification of the LLVM backend that I already plan to do in another branch, but I'd like to push the patch into `master`, and then merge from `master` into that branch. The LLVM backend attempts to trash the physical registers corresponding to Rx, Fx, and Dx registers that are caller-saved before an FFI call by emitting a sequence such as this: {{{#!llvm store i64 undef, i64* %R3_Var store i64 undef, i64* %R4_Var store i64 undef, i64* %R5_Var store i64 undef, i64* %R6_Var store float undef, float* %F1_Var store double undef, double* %D1_Var store float undef, float* %F2_Var store double undef, double* %D2_Var store float undef, float* %F3_Var store double undef, double* %D3_Var store float undef, float* %F4_Var store double undef, double* %D4_Var store float undef, float* %F5_Var store double undef, double* %D5_Var store float undef, float* %F6_Var store double undef, double* %D6_Var %ln7bu = call ccc double (double) @llvm.sin.f64( double %ln7bs ) nounwind }}} Where the Rx/Fx/Dx registers are chosen based on what physical register those global registers map to, and whether those physical registers are caller-saved according to the C ABI. I'm certain this is unnecessary, as there is no way to know the physical register corresponding to those vars within an LLVM IR function. The calling convention used for the FFI call will preserve caller-saved registers as needed, i.e., only if such a value is needed after the call. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 30 13:56:36 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 30 Jun 2017 13:56:36 -0000 Subject: [GHC] #13904: LLVM does not need to trash callee-saved registers. In-Reply-To: <044.9fbf455960cc2fbed77cfe6c815566aa@haskell.org> References: <044.9fbf455960cc2fbed77cfe6c815566aa@haskell.org> Message-ID: <059.2c62e01d912c4ee4f4aa2aa4c7e4f848@haskell.org> #13904: LLVM does not need to trash callee-saved registers. -------------------------------------+------------------------------------- Reporter: kavon | Owner: kavon Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: llvm, codegen Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: #4992 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by kavon): * owner: (none) => kavon -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 30 13:57:36 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 30 Jun 2017 13:57:36 -0000 Subject: [GHC] #13904: LLVM does not need to trash caller-saved registers. (was: LLVM does not need to trash callee-saved registers.) In-Reply-To: <044.9fbf455960cc2fbed77cfe6c815566aa@haskell.org> References: <044.9fbf455960cc2fbed77cfe6c815566aa@haskell.org> Message-ID: <059.daf61e8a19de3bba511060793a714520@haskell.org> #13904: LLVM does not need to trash caller-saved registers. -------------------------------------+------------------------------------- Reporter: kavon | Owner: kavon Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: llvm, codegen Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: #4992 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 30 15:01:30 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 30 Jun 2017 15:01:30 -0000 Subject: [GHC] #4210: LLVM: Dynamic Library Support In-Reply-To: <045.9da2e8588befc1a62c55be781a6ff87b@haskell.org> References: <045.9da2e8588befc1a62c55be781a6ff87b@haskell.org> Message-ID: <060.3c06d1582a6058502c388e5033d69879@haskell.org> #4210: LLVM: Dynamic Library Support -------------------------------------+------------------------------------- Reporter: dterei | Owner: dterei Type: feature request | Status: closed Priority: low | Milestone: 7.6.2 Component: Compiler (LLVM) | Version: 6.13 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Runtime crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): Indeed I do; it's been on my list for quite a while now. I'll kick off a build right now. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 30 15:54:22 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 30 Jun 2017 15:54:22 -0000 Subject: [GHC] #13893: Improved Help for Control.Concurrent and Control.Exception when "variable not in scope" In-Reply-To: <044.50a1c8e97ad1d72587a33a02855fe4cb@haskell.org> References: <044.50a1c8e97ad1d72587a33a02855fe4cb@haskell.org> Message-ID: <059.6c7b052b531596da6204c97f8f4ae984@haskell.org> #13893: Improved Help for Control.Concurrent and Control.Exception when "variable not in scope" -------------------------------------+------------------------------------- Reporter: vanto | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Poor/confusing | Unknown/Multiple error message | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by slyfox): * cc: slyfox (added) Comment: I have a few clarifying questions on this proposal. - Why take preference of packages coming with ghc in this case? It's not always the case that user wants to use '''base''''s primitives. I would say suggesting incorrect module imports would lead to more confusion. - Which procedure should define which packages (and modules) are blessed to deliver suggestions for symbols? For example, do '''xhtml''' or '''haskeline'' packages quialify as such? - As ticket's subject is worded why '''Control.Concurrent''' and '''Control.Exception''' should be threated special? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 30 16:01:03 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 30 Jun 2017 16:01:03 -0000 Subject: [GHC] #13903: KQueue evtmgr backend fails to register for write events In-Reply-To: <048.b40d50b7e059c68fc52d5bbd492f52b4@haskell.org> References: <048.b40d50b7e059c68fc52d5bbd492f52b4@haskell.org> Message-ID: <063.30fb63c8f48cb43929988ab6f610d702@haskell.org> #13903: KQueue evtmgr backend fails to register for write events -------------------------------------+------------------------------------- Reporter: waldheinz | Owner: (none) Type: bug | Status: patch Priority: normal | Milestone: 8.4.1 Component: Runtime System | Version: 8.0.2 Resolution: | Keywords: Operating System: FreeBSD | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3692 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => patch * differential: => Phab:D3692 * milestone: => 8.4.1 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 30 16:01:35 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 30 Jun 2017 16:01:35 -0000 Subject: [GHC] #13904: LLVM does not need to trash caller-saved registers. In-Reply-To: <044.9fbf455960cc2fbed77cfe6c815566aa@haskell.org> References: <044.9fbf455960cc2fbed77cfe6c815566aa@haskell.org> Message-ID: <059.a8adb2e4afd6b4cee9a02d488520bb30@haskell.org> #13904: LLVM does not need to trash caller-saved registers. -------------------------------------+------------------------------------- Reporter: kavon | Owner: kavon Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: llvm, codegen Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: #4992 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): Let us know when you have a patch, kavon. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 30 17:17:07 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 30 Jun 2017 17:17:07 -0000 Subject: [GHC] #13877: GHC panic: No skolem info: k2 In-Reply-To: <050.85aac3d842c3e1851a442a13f59ce985@haskell.org> References: <050.85aac3d842c3e1851a442a13f59ce985@haskell.org> Message-ID: <065.1e3420fd35cb08688a72a052d0df3510@haskell.org> #13877: GHC panic: No skolem info: k2 -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.1 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): Going back to the original program, if you change this line: {{{#!hs listElimTyFun = listElimPoly @(:->) @a @p @l }}} To this: {{{#!hs listElimTyFun = listElimPoly @(:->) }}} You get a different panic: {{{ $ /opt/ghc/8.2.1/bin/ghci Bug.hs GHCi, version 8.2.0.20170623: http://www.haskell.org/ghc/ :? for help Loaded GHCi configuration from /home/rgscott/.ghci [1 of 1] Compiling Eliminator ( Bug.hs, interpreted ) ghc: panic! (the 'impossible' happened) (GHC version 8.2.0.20170623 for x86_64-unknown-linux): piResultTy Fun [a_a5hm[sk:2]] (':->) * l_a5ho[sk:2] Call stack: CallStack (from HasCallStack): prettyCurrentCallStack, called at compiler/utils/Outputable.hs:1133:58 in ghc:Outputable callStackDoc, called at compiler/utils/Outputable.hs:1137:37 in ghc:Outputable pprPanic, called at compiler/types/Type.hs:948:35 in ghc:Type Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 30 17:27:15 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 30 Jun 2017 17:27:15 -0000 Subject: [GHC] #13905: ApplicativeDo is too strict with newtype patterns Message-ID: <045.00a8d56ab6c9231b9decf90394137e4f@haskell.org> #13905: ApplicativeDo is too strict with newtype patterns -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.4.1 Component: Compiler | Version: 8.3 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: GHC rejects Unknown/Multiple | valid program Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- The fix to #13875 went a little too far, and interprets newtype constructor patterns as strict. It's not clear to me how to fix this, as the `Name` of the constructor doesn't seem to give any clue as to whether it is a newtype constructor or a data constructor. The comment at the top of `basicTypes/Name.hs` indicates {{{ -- * 'Name.Name' is the type of names that have had their scoping and binding resolved. They -- have an 'OccName.OccName' but also a 'Unique.Unique' that disambiguates Names that have -- the same 'OccName.OccName' and indeed is used for all 'Name.Name' comparison. Names -- also contain information about where they originated from, see "Name#name_sorts" }}} which suggests that this information should be available, but I don't know what's involved in propagating it to the right place. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 30 17:36:35 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 30 Jun 2017 17:36:35 -0000 Subject: [GHC] #13541: Make it easier to use the gold linker In-Reply-To: <046.0b1321a637ed3292c60514e6510d2c09@haskell.org> References: <046.0b1321a637ed3292c60514e6510d2c09@haskell.org> Message-ID: <061.1a15018a370024d8c3fb8479a1752940@haskell.org> #13541: Make it easier to use the gold linker -------------------------------------+------------------------------------- Reporter: bgamari | Owner: (none) Type: feature request | Status: new Priority: highest | Milestone: 8.2.1 Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #13810, #13739 | Differential Rev(s): Phab:D3449, Wiki Page: | Phab:D3694 -------------------------------------+------------------------------------- Changes (by bgamari): * owner: bgamari => (none) * status: closed => new * differential: Phab:D3449 => Phab:D3449, Phab:D3694 * resolution: fixed => Comment: I found a bug in the above. See Phab:D3694 for the fix. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 30 17:36:45 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 30 Jun 2017 17:36:45 -0000 Subject: [GHC] #13541: Make it easier to use the gold linker In-Reply-To: <046.0b1321a637ed3292c60514e6510d2c09@haskell.org> References: <046.0b1321a637ed3292c60514e6510d2c09@haskell.org> Message-ID: <061.d48daa9ad1e39d991ed384c849298373@haskell.org> #13541: Make it easier to use the gold linker -------------------------------------+------------------------------------- Reporter: bgamari | Owner: (none) Type: feature request | Status: patch Priority: highest | Milestone: 8.2.1 Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #13810, #13739 | Differential Rev(s): Phab:D3449, Wiki Page: | Phab:D3694 -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => patch -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 30 18:07:53 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 30 Jun 2017 18:07:53 -0000 Subject: [GHC] #13906: ApplicativeDo doesn't handle existentials as well as it could Message-ID: <045.7a2a5b8fd2cc16f87e0125054276df67@haskell.org> #13906: ApplicativeDo doesn't handle existentials as well as it could -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.4.1 Component: Compiler | Version: 8.0.1 Keywords: ApplicativeDo | Operating System: Unknown/Multiple Architecture: | Type of failure: GHC rejects Unknown/Multiple | valid program Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- `ApplicativeDo` doesn't work nicely with existentials or GADTs. This was first considered in #13242, but I think it's worth reconsidering in light of #13875. In particular, we no longer need to think specially about whether a particular pattern match reveals evidence, as any pattern match that does so must necessarily be strict. Simon Marlow explains (in revised, I-think-unmerged, documentation) that {{{#!hs data T where A :: forall a . Eq a => a -> T test = do A x <- undefined _ <- return 'a' _ <- return 'b' return (x == x) }}} will not typecheck because it is first rearranged to {{{#!hs test = (\x _ -> x == x) <$> do A x <- undefined; _ <- return 'a'; return x <*> return 'b' }}} This is weird! The more human-obvious rearrangement would work just fine: {{{#!hs test = do A x <- undefined (\_ _ -> x == x) <$> return 'a' <*> return 'b' }}} How can we get there? I think it's actually easy. Suppose we have {{{#!hs do p1 <- e1 p2 <- e2 p3 <- e3 p4 <- e4 p5 <- e5 e6 }}} Before starting the detailed dependency analysis and such, let's look just at ''which patterns are strict''. If a pattern is strict, then ''every'' following action must be seen as depending on it, and therefore its bindings and evidence can scope over everything else. Let's say that `p3` is strict. Then we can immediately transform the expression to {{{#!hs do p1 <- e1 p2 <- e2 e3 >>= \case p3 -> do p4 <- e4 p5 <- e5 e6 -- if refutable _ -> fail ... }}} and then continue the process in the inner `do` block. If this is done as an initial pass, then further rearrangement doesn't need to consider the possibility of strict patterns; there won't be any. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 30 18:41:30 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 30 Jun 2017 18:41:30 -0000 Subject: [GHC] #13904: LLVM does not need to trash caller-saved registers. In-Reply-To: <044.9fbf455960cc2fbed77cfe6c815566aa@haskell.org> References: <044.9fbf455960cc2fbed77cfe6c815566aa@haskell.org> Message-ID: <059.e5088d7aed948c469ed08d93e1adad8e@haskell.org> #13904: LLVM does not need to trash caller-saved registers. -------------------------------------+------------------------------------- Reporter: kavon | Owner: kavon Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: llvm, codegen Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: #4992, #4308 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by kavon): * related: #4992 => #4992, #4308 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 30 18:50:12 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 30 Jun 2017 18:50:12 -0000 Subject: [GHC] #13434: hs_try_putmvar003 is timing out / segfaulting In-Reply-To: <045.a8ba4ff49dee16c0019e5f315e9937ac@haskell.org> References: <045.a8ba4ff49dee16c0019e5f315e9937ac@haskell.org> Message-ID: <060.1bf50f7527f61fad15b75a3573e004f9@haskell.org> #13434: hs_try_putmvar003 is timing out / segfaulting -------------------------------------+------------------------------------- Reporter: ezyang | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Runtime System | Version: 8.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Runtime crash | Test Case: Blocked By: | Blocking: 13722 Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): I can also reproduce the failure in my NixOS VM. Both my NixOS installation and jared-w's machine run glibc-2.25, whereas my usual development machine and Harbormaster both use 2.24. This may be causal or maybe not. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 30 19:25:53 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 30 Jun 2017 19:25:53 -0000 Subject: [GHC] #13905: ApplicativeDo is too strict with newtype patterns In-Reply-To: <045.00a8d56ab6c9231b9decf90394137e4f@haskell.org> References: <045.00a8d56ab6c9231b9decf90394137e4f@haskell.org> Message-ID: <060.f3848c941d79fa9a11b953375da06892@haskell.org> #13905: ApplicativeDo is too strict with newtype patterns -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.4.1 Component: Compiler | Version: 8.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonmar): I don't think this is fixable, I documented it in Phab:D3691 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 30 19:34:29 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 30 Jun 2017 19:34:29 -0000 Subject: [GHC] #13905: ApplicativeDo is too strict with newtype patterns In-Reply-To: <045.00a8d56ab6c9231b9decf90394137e4f@haskell.org> References: <045.00a8d56ab6c9231b9decf90394137e4f@haskell.org> Message-ID: <060.837544bfa443fb216040726b7c40431f@haskell.org> #13905: ApplicativeDo is too strict with newtype patterns -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.4.1 Component: Compiler | Version: 8.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by dfeuer): I'm not trying to be annoying, but may I ask why you don't think it's fixable? Don't we already know, at this point, where the constructor name comes from? I see the documentation, and the documentation is fine, but I suspect idiomatic code will run into this, and people will likely be surprised to see explicit `~` laziness around newtype constructors. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 30 19:39:53 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 30 Jun 2017 19:39:53 -0000 Subject: [GHC] #13906: ApplicativeDo doesn't handle existentials as well as it could In-Reply-To: <045.7a2a5b8fd2cc16f87e0125054276df67@haskell.org> References: <045.7a2a5b8fd2cc16f87e0125054276df67@haskell.org> Message-ID: <060.3bd2424eb40ce78335912c910cbb1cde@haskell.org> #13906: ApplicativeDo doesn't handle existentials as well as it could -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.4.1 Component: Compiler | Version: 8.0.1 Resolution: | Keywords: ApplicativeDo Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonmar): Well ok, but we're a bit down in the weeds here! Some other more important improvements we could make to ApplicativeDo are e.g. #10892 and #10976. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 30 19:45:44 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 30 Jun 2017 19:45:44 -0000 Subject: [GHC] #13905: ApplicativeDo is too strict with newtype patterns In-Reply-To: <045.00a8d56ab6c9231b9decf90394137e4f@haskell.org> References: <045.00a8d56ab6c9231b9decf90394137e4f@haskell.org> Message-ID: <060.7bfb9aea9bcf0117d5a339e2667c93f8@haskell.org> #13905: ApplicativeDo is too strict with newtype patterns -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.4.1 Component: Compiler | Version: 8.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonmar): We do ApplicativeDo rearrangement in the renamer, and we don't have the mapping from Names to TyThings until the typechecker, so at least superficially it seems hard. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 30 20:07:49 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 30 Jun 2017 20:07:49 -0000 Subject: [GHC] #13907: stack upgrade fails on Mac OS Message-ID: <045.69034993c5ec98845ad6df721992671d@haskell.org> #13907: stack upgrade fails on Mac OS -------------------------------------+------------------------------------- Reporter: gukoff | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- Configuring stack-1.4.0... stack-1.4.0: build Preprocessing library stack-1.4.0... [ 1 of 124] Compiling Text.PrettyPrint.Leijen.Extended ( src/Text/PrettyPrint/Leijen/Extended.hs, .stack- work/dist/x86_64-osx/Cabal-1.22.5.0/build/Text/PrettyPrint/Leijen/Extended.o ) [ 2 of 124] Compiling Hackage.Security.Client.Repository.HttpLib.HttpClient ( src/Hackage/Security/Client/Repository/HttpLib/HttpClient.hs, .stack- work/dist/x86_64-osx/Cabal-1.22.5.0/build/Hackage/Security/Client/Repository/HttpLib/HttpClient.o ) [ 3 of 124] Compiling Stack.Options.ScriptParser ( src/Stack/Options/ScriptParser.hs, .stack- work/dist/x86_64-osx/Cabal-1.22.5.0/build/Stack/Options/ScriptParser.o ) [ 4 of 124] Compiling Stack.Ghci.Script ( src/Stack/Ghci/Script.hs, .stack-work/dist/x86_64-osx/Cabal-1.22.5.0/build/Stack/Ghci/Script.o ) [ 5 of 124] Compiling Stack.FileWatch ( src/Stack/FileWatch.hs, .stack- work/dist/x86_64-osx/Cabal-1.22.5.0/build/Stack/FileWatch.o ) [ 6 of 124] Compiling System.Process.PagerEditor ( src/System/Process/PagerEditor.hs, .stack- work/dist/x86_64-osx/Cabal-1.22.5.0/build/System/Process/PagerEditor.o ) [ 7 of 124] Compiling System.Process.Log ( src/System/Process/Log.hs, .stack-work/dist/x86_64-osx/Cabal-1.22.5.0/build/System/Process/Log.o ) [ 8 of 124] Compiling Paths_stack ( .stack- work/dist/x86_64-osx/Cabal-1.22.5.0/build/autogen/Paths_stack.hs, .stack- work/dist/x86_64-osx/Cabal-1.22.5.0/build/Paths_stack.o ) [ 9 of 124] Compiling Path.Find ( src/Path/Find.hs, .stack- work/dist/x86_64-osx/Cabal-1.22.5.0/build/Path/Find.o ) [ 10 of 124] Compiling Path.Extra ( src/Path/Extra.hs, .stack- work/dist/x86_64-osx/Cabal-1.22.5.0/build/Path/Extra.o ) [ 11 of 124] Compiling System.Process.Read ( src/System/Process/Read.hs, .stack-work/dist/x86_64-osx/Cabal-1.22.5.0/build/System/Process/Read.o ) ghc: panic! (the 'impossible' happened) (GHC version 7.10.3 for x86_64-apple-darwin): Loading temp shared object failed: dlopen(/var/folders/tj/sfwy4my94nvdn8qx3l2cd97n_75vlr/T/ghc78750_0/libghc_68.dylib, 5): no suitable image found. Did find: /var/folders/tj/sfwy4my94nvdn8qx3l2cd97n_75vlr/T/ghc78750_0/libghc_68.dylib: malformed mach-o: load commands size (49568) > 32768 Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug Completed 26 action(s). -- While building package stack-1.4.0 using: /private/var/folders/tj/sfwy4my94nvdn8qx3l2cd97n_75vlr/T/stack- upgrade75916/stack-1.4.0/.stack- work/dist/x86_64-osx/Cabal-1.22.5.0/setup/setup --builddir=.stack- work/dist/x86_64-osx/Cabal-1.22.5.0 build lib:stack exe:stack --ghc- options " -ddump-hi -ddump-to-file" Process exited with code: ExitFailure 1 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jun 30 21:34:46 2017 From: ghc-devs at haskell.org (GHC) Date: Fri, 30 Jun 2017 21:34:46 -0000 Subject: [GHC] #13906: ApplicativeDo doesn't handle existentials as well as it could In-Reply-To: <045.7a2a5b8fd2cc16f87e0125054276df67@haskell.org> References: <045.7a2a5b8fd2cc16f87e0125054276df67@haskell.org> Message-ID: <060.034dd2ebf35b9a97582351d37b27f4f5@haskell.org> #13906: ApplicativeDo doesn't handle existentials as well as it could -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.4.1 Component: Compiler | Version: 8.0.1 Resolution: | Keywords: ApplicativeDo Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by dfeuer): Copied from Phab:D3691: simonmar: But the proposal in Trac #13906 loses some opportunities for parallelism. e.g. {{{#!hs do T x1 <- A x2 <- B[x1] T x2 <- C x4 <- D[x2] return (x2,x4) }}} and we want to get `(A;B) | (C;D)`, not `(A; (B|C); D)` ---- dfeuer: We do? I think we don't. Suppose we have {{{#!hs do () <- m n }}} Surely we only want to perform `n` if `m` successfully produces non-bottom `()`. The dependency is implicit. To get the parallelism, you need to eliminate the strict binding. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jun 12 09:33:39 2017 From: ghc-devs at haskell.org (GHC) Date: Mon, 12 Jun 2017 09:33:39 -0000 Subject: [GHC] #13816: make phase1 fails with clang error on Mac OS X El Capitan In-Reply-To: <044.dad7278a0f298c880e344d26abcde905@haskell.org> References: <044.dad7278a0f298c880e344d26abcde905@haskell.org> Message-ID: <059.05de2a523dd91d745686411707700c70@haskell.org> #13816: make phase1 fails with clang error on Mac OS X El Capitan -------------------------------------+------------------------------------- Reporter: bollu | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Description changed by bollu: @@ -4,1 +4,1 @@ - ╭─bollu at cantordust ~/work/ghc-all/ghc/libraries ‹2.3.1› ‹master*› + ╭─bollu at cantordust ~/work/ghc-all/ghc ‹2.3.1› ‹master*› @@ -6,3 +6,11 @@ - 130 ↵ - /Applications/Xcode.app/Contents/Developer/usr/bin/make -C .. - all_libraries + + test -f mk/config.mk.old + + cmp -s mk/config.mk mk/config.mk.old + touch -r mk/config.mk.old mk/config.mk + + test -f mk/project.mk.old + + cmp -s mk/project.mk mk/project.mk.old + + cp -p mk/project.mk mk/project.mk.old + touch -r mk/project.mk.old mk/project.mk + + test -f compiler/ghc.cabal.old + + cmp -s compiler/ghc.cabal compiler/ghc.cabal.old + + cp -p compiler/ghc.cabal compiler/ghc.cabal.old + touch -r compiler/ghc.cabal.old compiler/ghc.cabal @@ -12,1 +20,276 @@ - make[2]: Nothing to be done for `phase_0_builds'. + "rm" -f compiler/stage1/build/Config.hs + Creating compiler/stage1/build/Config.hs ... + done. + "inplace/bin/ghc-cabal" configure libraries/ghc-boot-th dist-boot "" + --with-ghc="/usr/local/bin/ghc" --with-ghc-pkg="/usr/local/bin/ghc-pkg" + --package-db=/Users/bollu/work/ghc-all/ghc/libraries/bootstrapping.conf + --disable-library-for-ghci --enable-library-vanilla --enable-library-for- + ghci --disable-library-profiling --disable-shared --configure- + option=CFLAGS="-Wall -fno-stack-protector -Wno-unknown-pragmas" + --configure-option=LDFLAGS=" " --configure-option=CPPFLAGS=" " --gcc- + options="-Wall -fno-stack-protector -Wno-unknown-pragmas " + --constraint "binary == 0.8.4.1" --constraint "Cabal == 2.0.0.0" + --constraint "hpc == 0.6.0.3" --constraint "ghc-boot-th == 8.3" + --constraint "ghc-boot == 8.3" --constraint "hoopl == 3.10.2.2" + --constraint "transformers == 0.5.2.0" --constraint "template-haskell == + 2.12.0.0" --constraint "ghci == 8.3" --constraint "terminfo == + 0.4.1.0" --with-gcc="clang" --with-ld="ld" --with-ar="/usr/bin/ar" --with- + alex="/Users/bollu/.local/bin/alex" --with- + happy="/Users/bollu/.local/bin/happy" + Configuring ghc-boot-th-8.3... + "/usr/local/bin/ghc-pkg" update -v0 --force --package- + db=libraries/bootstrapping.conf libraries/ghc-boot-th/dist-boot/inplace- + pkg-config + ghc-boot-th-8.3: Warning: Unrecognized field abi-depends on line 30 + ghc-boot-th-8.3: Warning: Unrecognized field indefinite on line 18 + ghc-boot-th-8.3: Warning: haddock-interfaces: /Users/bollu/work/ghc- + all/ghc/libraries/ghc-boot-th/dist-boot/doc/html/ghc-boot-th/ghc-boot- + th.haddock doesn't exist or isn't a file + "inplace/bin/ghc-cabal" configure libraries/ghc-boot dist-boot "" --with- + ghc="/usr/local/bin/ghc" --with-ghc-pkg="/usr/local/bin/ghc-pkg" + --package-db=/Users/bollu/work/ghc-all/ghc/libraries/bootstrapping.conf + --disable-library-for-ghci --enable-library-vanilla --enable-library-for- + ghci --disable-library-profiling --disable-shared --configure- + option=CFLAGS="-Wall -fno-stack-protector -Wno-unknown-pragmas" + --configure-option=LDFLAGS=" " --configure-option=CPPFLAGS=" " --gcc- + options="-Wall -fno-stack-protector -Wno-unknown-pragmas " + --constraint "binary == 0.8.4.1" --constraint "Cabal == 2.0.0.0" + --constraint "hpc == 0.6.0.3" --constraint "ghc-boot-th == 8.3" + --constraint "ghc-boot == 8.3" --constraint "hoopl == 3.10.2.2" + --constraint "transformers == 0.5.2.0" --constraint "template-haskell == + 2.12.0.0" --constraint "ghci == 8.3" --constraint "terminfo == + 0.4.1.0" --with-gcc="clang" --with-ld="ld" --with-ar="/usr/bin/ar" --with- + alex="/Users/bollu/.local/bin/alex" --with- + happy="/Users/bollu/.local/bin/happy" + Configuring ghc-boot-8.3... + "/usr/local/bin/ghc-pkg" update -v0 --force --package- + db=libraries/bootstrapping.conf libraries/ghc-boot/dist-boot/inplace-pkg- + config + ghc-boot-8.3: Warning: Unrecognized field abi-depends on line 37 + ghc-boot-8.3: Warning: Unrecognized field indefinite on line 23 + ghc-boot-8.3: Warning: haddock-interfaces: /Users/bollu/work/ghc- + all/ghc/libraries/ghc-boot/dist-boot/doc/html/ghc-boot/ghc-boot.haddock + doesn't exist or isn't a file + "inplace/bin/ghc-cabal" configure libraries/hoopl dist-boot "" --with- + ghc="/usr/local/bin/ghc" --with-ghc-pkg="/usr/local/bin/ghc-pkg" + --package-db=/Users/bollu/work/ghc-all/ghc/libraries/bootstrapping.conf + --disable-library-for-ghci --enable-library-vanilla --enable-library-for- + ghci --disable-library-profiling --disable-shared --configure- + option=CFLAGS="-Wall -fno-stack-protector -Wno-unknown-pragmas" + --configure-option=LDFLAGS=" " --configure-option=CPPFLAGS=" " --gcc- + options="-Wall -fno-stack-protector -Wno-unknown-pragmas " + --constraint "binary == 0.8.4.1" --constraint "Cabal == 2.0.0.0" + --constraint "hpc == 0.6.0.3" --constraint "ghc-boot-th == 8.3" + --constraint "ghc-boot == 8.3" --constraint "hoopl == 3.10.2.2" + --constraint "transformers == 0.5.2.0" --constraint "template-haskell == + 2.12.0.0" --constraint "ghci == 8.3" --constraint "terminfo == + 0.4.1.0" --with-gcc="clang" --with-ld="ld" --with-ar="/usr/bin/ar" --with- + alex="/Users/bollu/.local/bin/alex" --with- + happy="/Users/bollu/.local/bin/happy" + Configuring hoopl-3.10.2.2... + "/usr/local/bin/ghc-pkg" update -v0 --force --package- + db=libraries/bootstrapping.conf libraries/hoopl/dist-boot/inplace-pkg- + config + hoopl-3.10.2.2: Warning: Unrecognized field abi-depends on line 36 + hoopl-3.10.2.2: Warning: Unrecognized field indefinite on line 17 + hoopl-3.10.2.2: Warning: haddock-interfaces: /Users/bollu/work/ghc- + all/ghc/libraries/hoopl/dist-boot/doc/html/hoopl/hoopl.haddock doesn't + exist or isn't a file + "inplace/bin/ghc-cabal" configure libraries/transformers dist-boot "" + --with-ghc="/usr/local/bin/ghc" --with-ghc-pkg="/usr/local/bin/ghc-pkg" + --package-db=/Users/bollu/work/ghc-all/ghc/libraries/bootstrapping.conf + --disable-library-for-ghci --enable-library-vanilla --enable-library-for- + ghci --disable-library-profiling --disable-shared --configure- + option=CFLAGS="-Wall -fno-stack-protector -Wno-unknown-pragmas" + --configure-option=LDFLAGS=" " --configure-option=CPPFLAGS=" " --gcc- + options="-Wall -fno-stack-protector -Wno-unknown-pragmas " + --constraint "binary == 0.8.4.1" --constraint "Cabal == 2.0.0.0" + --constraint "hpc == 0.6.0.3" --constraint "ghc-boot-th == 8.3" + --constraint "ghc-boot == 8.3" --constraint "hoopl == 3.10.2.2" + --constraint "transformers == 0.5.2.0" --constraint "template-haskell == + 2.12.0.0" --constraint "ghci == 8.3" --constraint "terminfo == + 0.4.1.0" --with-gcc="clang" --with-ld="ld" --with-ar="/usr/bin/ar" --with- + alex="/Users/bollu/.local/bin/alex" --with- + happy="/Users/bollu/.local/bin/happy" + Configuring transformers-0.5.2.0... + "/usr/local/bin/ghc-pkg" update -v0 --force --package- + db=libraries/bootstrapping.conf libraries/transformers/dist-boot/inplace- + pkg-config + transformers-0.5.2.0: Warning: Unrecognized field abi-depends on line 55 + transformers-0.5.2.0: Warning: Unrecognized field indefinite on line 33 + transformers-0.5.2.0: Warning: haddock-interfaces: /Users/bollu/work/ghc- + all/ghc/libraries/transformers/dist- + boot/doc/html/transformers/transformers.haddock doesn't exist or isn't a + file + "inplace/bin/ghc-cabal" configure libraries/template-haskell dist-boot "" + --with-ghc="/usr/local/bin/ghc" --with-ghc-pkg="/usr/local/bin/ghc-pkg" + --package-db=/Users/bollu/work/ghc-all/ghc/libraries/bootstrapping.conf + --disable-library-for-ghci --enable-library-vanilla --enable-library-for- + ghci --disable-library-profiling --disable-shared --configure- + option=CFLAGS="-Wall -fno-stack-protector -Wno-unknown-pragmas" + --configure-option=LDFLAGS=" " --configure-option=CPPFLAGS=" " --gcc- + options="-Wall -fno-stack-protector -Wno-unknown-pragmas " + --constraint "binary == 0.8.4.1" --constraint "Cabal == 2.0.0.0" + --constraint "hpc == 0.6.0.3" --constraint "ghc-boot-th == 8.3" + --constraint "ghc-boot == 8.3" --constraint "hoopl == 3.10.2.2" + --constraint "transformers == 0.5.2.0" --constraint "template-haskell == + 2.12.0.0" --constraint "ghci == 8.3" --constraint "terminfo == + 0.4.1.0" --with-gcc="clang" --with-ld="ld" --with-ar="/usr/bin/ar" --with- + alex="/Users/bollu/.local/bin/alex" --with- + happy="/Users/bollu/.local/bin/happy" + Configuring template-haskell-2.12.0.0... + "/usr/local/bin/ghc-pkg" update -v0 --force --package- + db=libraries/bootstrapping.conf libraries/template-haskell/dist-boot + /inplace-pkg-config + template-haskell-2.12.0.0: Warning: Unrecognized field abi-depends on line + 32 + template-haskell-2.12.0.0: Warning: Unrecognized field indefinite on line + 16 + template-haskell-2.12.0.0: Warning: haddock-interfaces: /Users/bollu/work + /ghc-all/ghc/libraries/template-haskell/dist-boot/doc/html/template- + haskell/template-haskell.haddock doesn't exist or isn't a file + "inplace/bin/ghc-cabal" configure libraries/ghci dist-boot "" --with- + ghc="/usr/local/bin/ghc" --with-ghc-pkg="/usr/local/bin/ghc-pkg" + --package-db=/Users/bollu/work/ghc-all/ghc/libraries/bootstrapping.conf + --disable-library-for-ghci --enable-library-vanilla --enable-library-for- + ghci --disable-library-profiling --disable-shared --configure- + option=CFLAGS="-Wall -fno-stack-protector -Wno-unknown-pragmas" + --configure-option=LDFLAGS=" " --configure-option=CPPFLAGS=" " --gcc- + options="-Wall -fno-stack-protector -Wno-unknown-pragmas " + --constraint "binary == 0.8.4.1" --constraint "Cabal == 2.0.0.0" + --constraint "hpc == 0.6.0.3" --constraint "ghc-boot-th == 8.3" + --constraint "ghc-boot == 8.3" --constraint "hoopl == 3.10.2.2" + --constraint "transformers == 0.5.2.0" --constraint "template-haskell == + 2.12.0.0" --constraint "ghci == 8.3" --constraint "terminfo == + 0.4.1.0" --with-gcc="clang" --with-ld="ld" --with-ar="/usr/bin/ar" --with- + alex="/Users/bollu/.local/bin/alex" --with- + happy="/Users/bollu/.local/bin/happy" + Configuring ghci-8.3... + "/usr/local/bin/ghc-pkg" update -v0 --force --package- + db=libraries/bootstrapping.conf libraries/ghci/dist-boot/inplace-pkg- + config + ghci-8.3: Warning: Unrecognized field abi-depends on line 31 + ghci-8.3: Warning: Unrecognized field indefinite on line 14 + ghci-8.3: Warning: haddock-interfaces: /Users/bollu/work/ghc- + all/ghc/libraries/ghci/dist-boot/doc/html/ghci/ghci.haddock doesn't exist + or isn't a file + "inplace/bin/ghc-cabal" configure libraries/terminfo dist-boot "" --with- + ghc="/usr/local/bin/ghc" --with-ghc-pkg="/usr/local/bin/ghc-pkg" + --package-db=/Users/bollu/work/ghc-all/ghc/libraries/bootstrapping.conf + --disable-library-for-ghci --enable-library-vanilla --enable-library-for- + ghci --disable-library-profiling --disable-shared --configure- + option=CFLAGS="-Wall -fno-stack-protector -Wno-unknown-pragmas" + --configure-option=LDFLAGS=" " --configure-option=CPPFLAGS=" " --gcc- + options="-Wall -fno-stack-protector -Wno-unknown-pragmas " + --constraint "binary == 0.8.4.1" --constraint "Cabal == 2.0.0.0" + --constraint "hpc == 0.6.0.3" --constraint "ghc-boot-th == 8.3" + --constraint "ghc-boot == 8.3" --constraint "hoopl == 3.10.2.2" + --constraint "transformers == 0.5.2.0" --constraint "template-haskell == + 2.12.0.0" --constraint "ghci == 8.3" --constraint "terminfo == + 0.4.1.0" --with-gcc="clang" --with-ld="ld" --with-ar="/usr/bin/ar" --with- + alex="/Users/bollu/.local/bin/alex" --with- + happy="/Users/bollu/.local/bin/happy" + Configuring terminfo-0.4.1.0... + configure: WARNING: unrecognized options: --with-compiler + checking for gcc... /Users/bollu/work/LLVM- + all/polly/llvm_build_ninja/bin/clang + checking whether the C compiler works... yes + checking for C compiler default output file name... a.out + checking for suffix of executables... + checking whether we are cross compiling... no + checking for suffix of object files... o + checking whether we are using the GNU C compiler... yes + checking whether /Users/bollu/work/LLVM- + all/polly/llvm_build_ninja/bin/clang accepts -g... yes + checking for /Users/bollu/work/LLVM-all/polly/llvm_build_ninja/bin/clang + option to accept ISO C89... none needed + checking for setupterm in -ltinfo... no + checking for setupterm in -lncursesw... no + checking for setupterm in -lncurses... yes + configure: creating ./config.status + config.status: creating terminfo.buildinfo + configure: WARNING: unrecognized options: --with-compiler + "/usr/local/bin/ghc-pkg" update -v0 --force --package- + db=libraries/bootstrapping.conf libraries/terminfo/dist-boot/inplace-pkg- + config + terminfo-0.4.1.0: Warning: Unrecognized field abi-depends on line 35 + terminfo-0.4.1.0: Warning: Unrecognized field indefinite on line 18 + terminfo-0.4.1.0: Warning: haddock-interfaces: /Users/bollu/work/ghc- + all/ghc/libraries/terminfo/dist-boot/doc/html/terminfo/terminfo.haddock + doesn't exist or isn't a file + "inplace/bin/ghc-cabal" configure compiler stage1 "" --with- + ghc="/usr/local/bin/ghc" --with-ghc-pkg="/usr/local/bin/ghc-pkg" + --flags=stage1 --flags=ncg --ghc-option=-DSTAGE=1 --package- + db=/Users/bollu/work/ghc-all/ghc/libraries/bootstrapping.conf --disable- + library-for-ghci --enable-library-vanilla --enable-library-for-ghci + --disable-library-profiling --disable-shared --configure- + option=CFLAGS="-Wall -fno-stack-protector -Wno-unknown-pragmas" + --configure-option=LDFLAGS=" " --configure-option=CPPFLAGS=" -Iincludes + -Iincludes/dist -Iincludes/dist-derivedconstants/header -Iincludes/dist- + ghcconstants/header " --gcc-options="-Wall -fno-stack-protector -Wno- + unknown-pragmas " --constraint "binary == 0.8.4.1" --constraint + "Cabal == 2.0.0.0" --constraint "hpc == 0.6.0.3" --constraint "ghc- + boot-th == 8.3" --constraint "ghc-boot == 8.3" --constraint "hoopl == + 3.10.2.2" --constraint "transformers == 0.5.2.0" --constraint + "template-haskell == 2.12.0.0" --constraint "ghci == 8.3" --constraint + "terminfo == 0.4.1.0" --with-gcc="clang" --with-ld="ld" --with- + ar="/usr/bin/ar" --with-alex="/Users/bollu/.local/bin/alex" --with- + happy="/Users/bollu/.local/bin/happy" --disable-library-for-ghci + Configuring ghc-8.3... + Warning: 'license-file: ../LICENSE' is a relative path outside of the + source + tree. This will not work when generating a tarball with 'sdist'. + "/usr/local/bin/ghc-pkg" update -v0 --force --package- + db=libraries/bootstrapping.conf compiler/stage1/inplace-pkg-config + ghc-8.3: Warning: Unrecognized field abi-depends on line 125 + ghc-8.3: Warning: Unrecognized field indefinite on line 19 + ghc-8.3: Warning: haddock-interfaces: /Users/bollu/work/ghc- + all/ghc/compiler/stage1/doc/html/ghc/ghc.haddock doesn't exist or isn't a + file + "inplace/bin/ghc-cabal" configure ghc stage1 "" --with- + ghc="/usr/local/bin/ghc" --with-ghc-pkg="/usr/local/bin/ghc-pkg" + --flags=stage1 --package-db=/Users/bollu/work/ghc- + all/ghc/libraries/bootstrapping.conf --disable-library-for-ghci --disable- + library-vanilla --disable-library-profiling --disable-shared --configure- + option=CFLAGS="-Wall -fno-stack-protector -Wno-unknown-pragmas" + --configure-option=LDFLAGS=" " --configure-option=CPPFLAGS=" " --gcc- + options="-Wall -fno-stack-protector -Wno-unknown-pragmas " + --constraint "binary == 0.8.4.1" --constraint "Cabal == 2.0.0.0" + --constraint "hpc == 0.6.0.3" --constraint "ghc-boot-th == 8.3" + --constraint "ghc-boot == 8.3" --constraint "hoopl == 3.10.2.2" + --constraint "transformers == 0.5.2.0" --constraint "template-haskell == + 2.12.0.0" --constraint "ghci == 8.3" --constraint "terminfo == + 0.4.1.0" --with-gcc="clang" --with-ld="ld" --with-ar="/usr/bin/ar" --with- + alex="/Users/bollu/.local/bin/alex" --with- + happy="/Users/bollu/.local/bin/happy" + Configuring ghc-bin-8.3.20170608... + Warning: 'data-dir: ..' is a relative path outside of the source tree. + This + will not work when generating a tarball with 'sdist'. + "rm" -f utils/ghc-pkg/dist/build/Version.hs + echo "module Version where" >> utils/ghc- + pkg/dist/build/Version.hs + echo "version, targetOS, targetARCH :: String" >> utils/ghc- + pkg/dist/build/Version.hs + echo "version = \"8.3.20170608\"" >> utils/ghc- + pkg/dist/build/Version.hs + echo "targetOS = \"darwin\"" >> utils/ghc- + pkg/dist/build/Version.hs + echo "targetARCH = \"x86_64\"" >> utils/ghc-pkg/dist/build/Version.hs + "inplace/bin/ghc-cabal" configure utils/ghc-pkg dist "" --with- + ghc="/usr/local/bin/ghc" --with-ghc-pkg="/usr/local/bin/ghc-pkg" + --package-db=/Users/bollu/work/ghc-all/ghc/libraries/bootstrapping.conf + --disable-library-for-ghci --disable-library-vanilla --disable-library- + profiling --disable-shared --configure-option=CFLAGS="-Wall -fno-stack- + protector -Wno-unknown-pragmas" --configure-option=LDFLAGS=" " + --configure-option=CPPFLAGS=" -DWITH_TERMINFO" --gcc-options="-Wall + -fno-stack-protector -Wno-unknown-pragmas " --constraint "binary == + 0.8.4.1" --constraint "Cabal == 2.0.0.0" --constraint "hpc == 0.6.0.3" + --constraint "ghc-boot-th == 8.3" --constraint "ghc-boot == 8.3" + --constraint "hoopl == 3.10.2.2" --constraint "transformers == 0.5.2.0" + --constraint "template-haskell == 2.12.0.0" --constraint "ghci == 8.3" + --constraint "terminfo == 0.4.1.0" --with-gcc="clang" --with-ld="ld" + --with-ar="/usr/bin/ar" --with-alex="/Users/bollu/.local/bin/alex" --with- + happy="/Users/bollu/.local/bin/happy" + Configuring ghc-pkg-6.9... + make[1]: Nothing to be done for `phase_0_builds'. @@ -56,4 +339,0 @@ - libraries/text/ghc.mk:3: libraries/text/dist-boot/build/.depend-v.haskell: - No such file or directory - libraries/text/ghc.mk:3: libraries/text/dist-boot/build/.depend-v.c_asm: - No such file or directory @@ -68,1 +347,1 @@ - compiler/ghc.mk:590: compiler/stage1/build/.depend-v.haskell: No such file + compiler/ghc.mk:592: compiler/stage1/build/.depend-v.haskell: No such file @@ -72,0 +351,28 @@ + "rm" -f compiler/stage1/ghc_boot_platform.h + Creating compiler/stage1/ghc_boot_platform.h... + Done. + "rm" -f ghc/stage1/build/.depend.haskell.tmp + "/usr/local/bin/ghc" -M -static -H32m -O -Wall -package-db + libraries/bootstrapping.conf -hide-all-packages -i -ighc/. + -ighc/stage1/build -Ighc/stage1/build -ighc/stage1/build/ghc/autogen + -Ighc/stage1/build/ghc/autogen -optP-include + -optPghc/stage1/build/ghc/autogen/cabal_macros.h -package-id base-4.9.1.0 + -package-id array-0.5.1.1 -package-id bytestring-0.10.8.1 -package-id + directory-1.3.0.0 -package-id process-1.4.3.0 -package-id filepath-1.4.1.1 + -package-id ghc-boot-8.3 -package-id ghc-8.3 -package-id unix-2.7.2.1 + -Wall -XHaskell2010 -no-hs-main -no-user-package-db -rtsopts + -odir ghc/stage1/build -hidir ghc/stage1/build -stubdir ghc/stage1/build + -dep-makefile ghc/stage1/build/.depend.haskell.tmp -dep-suffix "" + -include-pkg-deps ghc/./Main.hs + echo "ghc_stage1_depfile_haskell_EXISTS = YES" >> + ghc/stage1/build/.depend.haskell.tmp + for dir in ghc/stage1/build/./; do if test ! -d $dir; then mkdir -p $dir; + fi done + grep -v ' : [a-zA-Z]:/' ghc/stage1/build/.depend.haskell.tmp > + ghc/stage1/build/.depend.haskell.tmp2 + sed -e '/hs$/ p' -e '/hs$/ s/o /hi /g' -e '/hs$/ s/:/ : %hi: %o /' -e + '/hs$/ s/^/$(eval $(call hi-rule,/' -e '/hs$/ s/$/))/' -e '/hs-boot$/ p' + -e '/hs-boot$/ s/o-boot /hi-boot /g' -e '/hs-boot$/ s/:/ : %hi-boot: + %o-boot /' -e '/hs-boot$/ s/^/$(eval $(call hi-rule,/' -e '/hs-boot$/ + s/$/))/' ghc/stage1/build/.depend.haskell.tmp2 > + ghc/stage1/build/.depend.haskell @@ -96,2 +403,1 @@ - make[2]: *** [utils/ghc-pkg/dist/build/.depend.haskell] Error 1 - make[1]: *** [all_libraries] Error 2 + make[1]: *** [utils/ghc-pkg/dist/build/.depend.haskell] Error 1 New description: `make` fails with the following build output at phase1: {{{ ╭─bollu at cantordust ~/work/ghc-all/ghc ‹2.3.1› ‹master*› ╰─$ export CC=gcc; export CXX=g++; CC=gcc CXX=g++ make + test -f mk/config.mk.old + cmp -s mk/config.mk mk/config.mk.old touch -r mk/config.mk.old mk/config.mk + test -f mk/project.mk.old + cmp -s mk/project.mk mk/project.mk.old + cp -p mk/project.mk mk/project.mk.old touch -r mk/project.mk.old mk/project.mk + test -f compiler/ghc.cabal.old + cmp -s compiler/ghc.cabal compiler/ghc.cabal.old + cp -p compiler/ghc.cabal compiler/ghc.cabal.old touch -r compiler/ghc.cabal.old compiler/ghc.cabal ===--- building phase 0 /Applications/Xcode.app/Contents/Developer/usr/bin/make --no-print- directory -f ghc.mk phase=0 phase_0_builds "rm" -f compiler/stage1/build/Config.hs Creating compiler/stage1/build/Config.hs ... done. "inplace/bin/ghc-cabal" configure libraries/ghc-boot-th dist-boot "" --with-ghc="/usr/local/bin/ghc" --with-ghc-pkg="/usr/local/bin/ghc-pkg" --package-db=/Users/bollu/work/ghc-all/ghc/libraries/bootstrapping.conf --disable-library-for-ghci --enable-library-vanilla --enable-library-for- ghci --disable-library-profiling --disable-shared --configure- option=CFLAGS="-Wall -fno-stack-protector -Wno-unknown-pragmas" --configure-option=LDFLAGS=" " --configure-option=CPPFLAGS=" " --gcc- options="-Wall -fno-stack-protector -Wno-unknown-pragmas " --constraint "binary == 0.8.4.1" --constraint "Cabal == 2.0.0.0" --constraint "hpc == 0.6.0.3" --constraint "ghc-boot-th == 8.3" --constraint "ghc-boot == 8.3" --constraint "hoopl == 3.10.2.2" --constraint "transformers == 0.5.2.0" --constraint "template-haskell == 2.12.0.0" --constraint "ghci == 8.3" --constraint "terminfo == 0.4.1.0" --with-gcc="clang" --with-ld="ld" --with-ar="/usr/bin/ar" --with- alex="/Users/bollu/.local/bin/alex" --with- happy="/Users/bollu/.local/bin/happy" Configuring ghc-boot-th-8.3... "/usr/local/bin/ghc-pkg" update -v0 --force --package- db=libraries/bootstrapping.conf libraries/ghc-boot-th/dist-boot/inplace- pkg-config ghc-boot-th-8.3: Warning: Unrecognized field abi-depends on line 30 ghc-boot-th-8.3: Warning: Unrecognized field indefinite on line 18 ghc-boot-th-8.3: Warning: haddock-interfaces: /Users/bollu/work/ghc- all/ghc/libraries/ghc-boot-th/dist-boot/doc/html/ghc-boot-th/ghc-boot- th.haddock doesn't exist or isn't a file "inplace/bin/ghc-cabal" configure libraries/ghc-boot dist-boot "" --with- ghc="/usr/local/bin/ghc" --with-ghc-pkg="/usr/local/bin/ghc-pkg" --package-db=/Users/bollu/work/ghc-all/ghc/libraries/bootstrapping.conf --disable-library-for-ghci --enable-library-vanilla --enable-library-for- ghci --disable-library-profiling --disable-shared --configure- option=CFLAGS="-Wall -fno-stack-protector -Wno-unknown-pragmas" --configure-option=LDFLAGS=" " --configure-option=CPPFLAGS=" " --gcc- options="-Wall -fno-stack-protector -Wno-unknown-pragmas " --constraint "binary == 0.8.4.1" --constraint "Cabal == 2.0.0.0" --constraint "hpc == 0.6.0.3" --constraint "ghc-boot-th == 8.3" --constraint "ghc-boot == 8.3" --constraint "hoopl == 3.10.2.2" --constraint "transformers == 0.5.2.0" --constraint "template-haskell == 2.12.0.0" --constraint "ghci == 8.3" --constraint "terminfo == 0.4.1.0" --with-gcc="clang" --with-ld="ld" --with-ar="/usr/bin/ar" --with- alex="/Users/bollu/.local/bin/alex" --with- happy="/Users/bollu/.local/bin/happy" Configuring ghc-boot-8.3... "/usr/local/bin/ghc-pkg" update -v0 --force --package- db=libraries/bootstrapping.conf libraries/ghc-boot/dist-boot/inplace-pkg- config ghc-boot-8.3: Warning: Unrecognized field abi-depends on line 37 ghc-boot-8.3: Warning: Unrecognized field indefinite on line 23 ghc-boot-8.3: Warning: haddock-interfaces: /Users/bollu/work/ghc- all/ghc/libraries/ghc-boot/dist-boot/doc/html/ghc-boot/ghc-boot.haddock doesn't exist or isn't a file "inplace/bin/ghc-cabal" configure libraries/hoopl dist-boot "" --with- ghc="/usr/local/bin/ghc" --with-ghc-pkg="/usr/local/bin/ghc-pkg" --package-db=/Users/bollu/work/ghc-all/ghc/libraries/bootstrapping.conf --disable-library-for-ghci --enable-library-vanilla --enable-library-for- ghci --disable-library-profiling --disable-shared --configure- option=CFLAGS="-Wall -fno-stack-protector -Wno-unknown-pragmas" --configure-option=LDFLAGS=" " --configure-option=CPPFLAGS=" " --gcc- options="-Wall -fno-stack-protector -Wno-unknown-pragmas " --constraint "binary == 0.8.4.1" --constraint "Cabal == 2.0.0.0" --constraint "hpc == 0.6.0.3" --constraint "ghc-boot-th == 8.3" --constraint "ghc-boot == 8.3" --constraint "hoopl == 3.10.2.2" --constraint "transformers == 0.5.2.0" --constraint "template-haskell == 2.12.0.0" --constraint "ghci == 8.3" --constraint "terminfo == 0.4.1.0" --with-gcc="clang" --with-ld="ld" --with-ar="/usr/bin/ar" --with- alex="/Users/bollu/.local/bin/alex" --with- happy="/Users/bollu/.local/bin/happy" Configuring hoopl-3.10.2.2... "/usr/local/bin/ghc-pkg" update -v0 --force --package- db=libraries/bootstrapping.conf libraries/hoopl/dist-boot/inplace-pkg- config hoopl-3.10.2.2: Warning: Unrecognized field abi-depends on line 36 hoopl-3.10.2.2: Warning: Unrecognized field indefinite on line 17 hoopl-3.10.2.2: Warning: haddock-interfaces: /Users/bollu/work/ghc- all/ghc/libraries/hoopl/dist-boot/doc/html/hoopl/hoopl.haddock doesn't exist or isn't a file "inplace/bin/ghc-cabal" configure libraries/transformers dist-boot "" --with-ghc="/usr/local/bin/ghc" --with-ghc-pkg="/usr/local/bin/ghc-pkg" --package-db=/Users/bollu/work/ghc-all/ghc/libraries/bootstrapping.conf --disable-library-for-ghci --enable-library-vanilla --enable-library-for- ghci --disable-library-profiling --disable-shared --configure- option=CFLAGS="-Wall -fno-stack-protector -Wno-unknown-pragmas" --configure-option=LDFLAGS=" " --configure-option=CPPFLAGS=" " --gcc- options="-Wall -fno-stack-protector -Wno-unknown-pragmas " --constraint "binary == 0.8.4.1" --constraint "Cabal == 2.0.0.0" --constraint "hpc == 0.6.0.3" --constraint "ghc-boot-th == 8.3" --constraint "ghc-boot == 8.3" --constraint "hoopl == 3.10.2.2" --constraint "transformers == 0.5.2.0" --constraint "template-haskell == 2.12.0.0" --constraint "ghci == 8.3" --constraint "terminfo == 0.4.1.0" --with-gcc="clang" --with-ld="ld" --with-ar="/usr/bin/ar" --with- alex="/Users/bollu/.local/bin/alex" --with- happy="/Users/bollu/.local/bin/happy" Configuring transformers-0.5.2.0... "/usr/local/bin/ghc-pkg" update -v0 --force --package- db=libraries/bootstrapping.conf libraries/transformers/dist-boot/inplace- pkg-config transformers-0.5.2.0: Warning: Unrecognized field abi-depends on line 55 transformers-0.5.2.0: Warning: Unrecognized field indefinite on line 33 transformers-0.5.2.0: Warning: haddock-interfaces: /Users/bollu/work/ghc- all/ghc/libraries/transformers/dist- boot/doc/html/transformers/transformers.haddock doesn't exist or isn't a file "inplace/bin/ghc-cabal" configure libraries/template-haskell dist-boot "" --with-ghc="/usr/local/bin/ghc" --with-ghc-pkg="/usr/local/bin/ghc-pkg" --package-db=/Users/bollu/work/ghc-all/ghc/libraries/bootstrapping.conf --disable-library-for-ghci --enable-library-vanilla --enable-library-for- ghci --disable-library-profiling --disable-shared --configure- option=CFLAGS="-Wall -fno-stack-protector -Wno-unknown-pragmas" --configure-option=LDFLAGS=" " --configure-option=CPPFLAGS=" " --gcc- options="-Wall -fno-stack-protector -Wno-unknown-pragmas " --constraint "binary == 0.8.4.1" --constraint "Cabal == 2.0.0.0" --constraint "hpc == 0.6.0.3" --constraint "ghc-boot-th == 8.3" --constraint "ghc-boot == 8.3" --constraint "hoopl == 3.10.2.2" --constraint "transformers == 0.5.2.0" --constraint "template-haskell == 2.12.0.0" --constraint "ghci == 8.3" --constraint "terminfo == 0.4.1.0" --with-gcc="clang" --with-ld="ld" --with-ar="/usr/bin/ar" --with- alex="/Users/bollu/.local/bin/alex" --with- happy="/Users/bollu/.local/bin/happy" Configuring template-haskell-2.12.0.0... "/usr/local/bin/ghc-pkg" update -v0 --force --package- db=libraries/bootstrapping.conf libraries/template-haskell/dist-boot /inplace-pkg-config template-haskell-2.12.0.0: Warning: Unrecognized field abi-depends on line 32 template-haskell-2.12.0.0: Warning: Unrecognized field indefinite on line 16 template-haskell-2.12.0.0: Warning: haddock-interfaces: /Users/bollu/work /ghc-all/ghc/libraries/template-haskell/dist-boot/doc/html/template- haskell/template-haskell.haddock doesn't exist or isn't a file "inplace/bin/ghc-cabal" configure libraries/ghci dist-boot "" --with- ghc="/usr/local/bin/ghc" --with-ghc-pkg="/usr/local/bin/ghc-pkg" --package-db=/Users/bollu/work/ghc-all/ghc/libraries/bootstrapping.conf --disable-library-for-ghci --enable-library-vanilla --enable-library-for- ghci --disable-library-profiling --disable-shared --configure- option=CFLAGS="-Wall -fno-stack-protector -Wno-unknown-pragmas" --configure-option=LDFLAGS=" " --configure-option=CPPFLAGS=" " --gcc- options="-Wall -fno-stack-protector -Wno-unknown-pragmas " --constraint "binary == 0.8.4.1" --constraint "Cabal == 2.0.0.0" --constraint "hpc == 0.6.0.3" --constraint "ghc-boot-th == 8.3" --constraint "ghc-boot == 8.3" --constraint "hoopl == 3.10.2.2" --constraint "transformers == 0.5.2.0" --constraint "template-haskell == 2.12.0.0" --constraint "ghci == 8.3" --constraint "terminfo == 0.4.1.0" --with-gcc="clang" --with-ld="ld" --with-ar="/usr/bin/ar" --with- alex="/Users/bollu/.local/bin/alex" --with- happy="/Users/bollu/.local/bin/happy" Configuring ghci-8.3... "/usr/local/bin/ghc-pkg" update -v0 --force --package- db=libraries/bootstrapping.conf libraries/ghci/dist-boot/inplace-pkg- config ghci-8.3: Warning: Unrecognized field abi-depends on line 31 ghci-8.3: Warning: Unrecognized field indefinite on line 14 ghci-8.3: Warning: haddock-interfaces: /Users/bollu/work/ghc- all/ghc/libraries/ghci/dist-boot/doc/html/ghci/ghci.haddock doesn't exist or isn't a file "inplace/bin/ghc-cabal" configure libraries/terminfo dist-boot "" --with- ghc="/usr/local/bin/ghc" --with-ghc-pkg="/usr/local/bin/ghc-pkg" --package-db=/Users/bollu/work/ghc-all/ghc/libraries/bootstrapping.conf --disable-library-for-ghci --enable-library-vanilla --enable-library-for- ghci --disable-library-profiling --disable-shared --configure- option=CFLAGS="-Wall -fno-stack-protector -Wno-unknown-pragmas" --configure-option=LDFLAGS=" " --configure-option=CPPFLAGS=" " --gcc- options="-Wall -fno-stack-protector -Wno-unknown-pragmas " --constraint "binary == 0.8.4.1" --constraint "Cabal == 2.0.0.0" --constraint "hpc == 0.6.0.3" --constraint "ghc-boot-th == 8.3" --constraint "ghc-boot == 8.3" --constraint "hoopl == 3.10.2.2" --constraint "transformers == 0.5.2.0" --constraint "template-haskell == 2.12.0.0" --constraint "ghci == 8.3" --constraint "terminfo == 0.4.1.0" --with-gcc="clang" --with-ld="ld" --with-ar="/usr/bin/ar" --with- alex="/Users/bollu/.local/bin/alex" --with- happy="/Users/bollu/.local/bin/happy" Configuring terminfo-0.4.1.0... configure: WARNING: unrecognized options: --with-compiler checking for gcc... /Users/bollu/work/LLVM- all/polly/llvm_build_ninja/bin/clang checking whether the C compiler works... yes checking for C compiler default output file name... a.out checking for suffix of executables... checking whether we are cross compiling... no checking for suffix of object files... o checking whether we are using the GNU C compiler... yes checking whether /Users/bollu/work/LLVM- all/polly/llvm_build_ninja/bin/clang accepts -g... yes checking for /Users/bollu/work/LLVM-all/polly/llvm_build_ninja/bin/clang option to accept ISO C89... none needed checking for setupterm in -ltinfo... no checking for setupterm in -lncursesw... no checking for setupterm in -lncurses... yes configure: creating ./config.status config.status: creating terminfo.buildinfo configure: WARNING: unrecognized options: --with-compiler "/usr/local/bin/ghc-pkg" update -v0 --force --package- db=libraries/bootstrapping.conf libraries/terminfo/dist-boot/inplace-pkg- config terminfo-0.4.1.0: Warning: Unrecognized field abi-depends on line 35 terminfo-0.4.1.0: Warning: Unrecognized field indefinite on line 18 terminfo-0.4.1.0: Warning: haddock-interfaces: /Users/bollu/work/ghc- all/ghc/libraries/terminfo/dist-boot/doc/html/terminfo/terminfo.haddock doesn't exist or isn't a file "inplace/bin/ghc-cabal" configure compiler stage1 "" --with- ghc="/usr/local/bin/ghc" --with-ghc-pkg="/usr/local/bin/ghc-pkg" --flags=stage1 --flags=ncg --ghc-option=-DSTAGE=1 --package- db=/Users/bollu/work/ghc-all/ghc/libraries/bootstrapping.conf --disable- library-for-ghci --enable-library-vanilla --enable-library-for-ghci --disable-library-profiling --disable-shared --configure- option=CFLAGS="-Wall -fno-stack-protector -Wno-unknown-pragmas" --configure-option=LDFLAGS=" " --configure-option=CPPFLAGS=" -Iincludes -Iincludes/dist -Iincludes/dist-derivedconstants/header -Iincludes/dist- ghcconstants/header " --gcc-options="-Wall -fno-stack-protector -Wno- unknown-pragmas " --constraint "binary == 0.8.4.1" --constraint "Cabal == 2.0.0.0" --constraint "hpc == 0.6.0.3" --constraint "ghc- boot-th == 8.3" --constraint "ghc-boot == 8.3" --constraint "hoopl == 3.10.2.2" --constraint "transformers == 0.5.2.0" --constraint "template-haskell == 2.12.0.0" --constraint "ghci == 8.3" --constraint "terminfo == 0.4.1.0" --with-gcc="clang" --with-ld="ld" --with- ar="/usr/bin/ar" --with-alex="/Users/bollu/.local/bin/alex" --with- happy="/Users/bollu/.local/bin/happy" --disable-library-for-ghci Configuring ghc-8.3... Warning: 'license-file: ../LICENSE' is a relative path outside of the source tree. This will not work when generating a tarball with 'sdist'. "/usr/local/bin/ghc-pkg" update -v0 --force --package- db=libraries/bootstrapping.conf compiler/stage1/inplace-pkg-config ghc-8.3: Warning: Unrecognized field abi-depends on line 125 ghc-8.3: Warning: Unrecognized field indefinite on line 19 ghc-8.3: Warning: haddock-interfaces: /Users/bollu/work/ghc- all/ghc/compiler/stage1/doc/html/ghc/ghc.haddock doesn't exist or isn't a file "inplace/bin/ghc-cabal" configure ghc stage1 "" --with- ghc="/usr/local/bin/ghc" --with-ghc-pkg="/usr/local/bin/ghc-pkg" --flags=stage1 --package-db=/Users/bollu/work/ghc- all/ghc/libraries/bootstrapping.conf --disable-library-for-ghci --disable- library-vanilla --disable-library-profiling --disable-shared --configure- option=CFLAGS="-Wall -fno-stack-protector -Wno-unknown-pragmas" --configure-option=LDFLAGS=" " --configure-option=CPPFLAGS=" " --gcc- options="-Wall -fno-stack-protector -Wno-unknown-pragmas " --constraint "binary == 0.8.4.1" --constraint "Cabal == 2.0.0.0" --constraint "hpc == 0.6.0.3" --constraint "ghc-boot-th == 8.3" --constraint "ghc-boot == 8.3" --constraint "hoopl == 3.10.2.2" --constraint "transformers == 0.5.2.0" --constraint "template-haskell == 2.12.0.0" --constraint "ghci == 8.3" --constraint "terminfo == 0.4.1.0" --with-gcc="clang" --with-ld="ld" --with-ar="/usr/bin/ar" --with- alex="/Users/bollu/.local/bin/alex" --with- happy="/Users/bollu/.local/bin/happy" Configuring ghc-bin-8.3.20170608... Warning: 'data-dir: ..' is a relative path outside of the source tree. This will not work when generating a tarball with 'sdist'. "rm" -f utils/ghc-pkg/dist/build/Version.hs echo "module Version where" >> utils/ghc- pkg/dist/build/Version.hs echo "version, targetOS, targetARCH :: String" >> utils/ghc- pkg/dist/build/Version.hs echo "version = \"8.3.20170608\"" >> utils/ghc- pkg/dist/build/Version.hs echo "targetOS = \"darwin\"" >> utils/ghc- pkg/dist/build/Version.hs echo "targetARCH = \"x86_64\"" >> utils/ghc-pkg/dist/build/Version.hs "inplace/bin/ghc-cabal" configure utils/ghc-pkg dist "" --with- ghc="/usr/local/bin/ghc" --with-ghc-pkg="/usr/local/bin/ghc-pkg" --package-db=/Users/bollu/work/ghc-all/ghc/libraries/bootstrapping.conf --disable-library-for-ghci --disable-library-vanilla --disable-library- profiling --disable-shared --configure-option=CFLAGS="-Wall -fno-stack- protector -Wno-unknown-pragmas" --configure-option=LDFLAGS=" " --configure-option=CPPFLAGS=" -DWITH_TERMINFO" --gcc-options="-Wall -fno-stack-protector -Wno-unknown-pragmas " --constraint "binary == 0.8.4.1" --constraint "Cabal == 2.0.0.0" --constraint "hpc == 0.6.0.3" --constraint "ghc-boot-th == 8.3" --constraint "ghc-boot == 8.3" --constraint "hoopl == 3.10.2.2" --constraint "transformers == 0.5.2.0" --constraint "template-haskell == 2.12.0.0" --constraint "ghci == 8.3" --constraint "terminfo == 0.4.1.0" --with-gcc="clang" --with-ld="ld" --with-ar="/usr/bin/ar" --with-alex="/Users/bollu/.local/bin/alex" --with- happy="/Users/bollu/.local/bin/happy" Configuring ghc-pkg-6.9... make[1]: Nothing to be done for `phase_0_builds'. ===--- building phase 1 /Applications/Xcode.app/Contents/Developer/usr/bin/make --no-print- directory -f ghc.mk phase=1 phase_1_builds utils/unlit/ghc.mk:33: utils/unlit/dist/build/.depend.c_asm: No such file or directory utils/hp2ps/ghc.mk:43: utils/hp2ps/dist/build/.depend.c_asm: No such file or directory utils/genapply/ghc.mk:23: utils/genapply/dist/build/.depend.haskell: No such file or directory utils/genapply/ghc.mk:23: utils/genapply/dist/build/.depend.c_asm: No such file or directory libraries/hpc/ghc.mk:3: libraries/hpc/dist-boot/build/.depend-v.haskell: No such file or directory libraries/hpc/ghc.mk:3: libraries/hpc/dist-boot/build/.depend-v.c_asm: No such file or directory libraries/binary/ghc.mk:3: libraries/binary/dist- boot/build/.depend-v.haskell: No such file or directory libraries/binary/ghc.mk:3: libraries/binary/dist- boot/build/.depend-v.c_asm: No such file or directory libraries/Cabal/Cabal/ghc.mk:3: libraries/Cabal/Cabal/dist- boot/build/.depend-v.haskell: No such file or directory libraries/Cabal/Cabal/ghc.mk:3: libraries/Cabal/Cabal/dist- boot/build/.depend-v.c_asm: No such file or directory libraries/ghc-boot-th/ghc.mk:3: libraries/ghc-boot-th/dist- boot/build/.depend-v.haskell: No such file or directory libraries/ghc-boot-th/ghc.mk:3: libraries/ghc-boot-th/dist- boot/build/.depend-v.c_asm: No such file or directory libraries/ghc-boot/ghc.mk:3: libraries/ghc-boot/dist- boot/build/.depend-v.haskell: No such file or directory libraries/ghc-boot/ghc.mk:3: libraries/ghc-boot/dist- boot/build/.depend-v.c_asm: No such file or directory libraries/template-haskell/ghc.mk:3: libraries/template-haskell/dist- boot/build/.depend-v.haskell: No such file or directory libraries/template-haskell/ghc.mk:3: libraries/template-haskell/dist- boot/build/.depend-v.c_asm: No such file or directory libraries/hoopl/ghc.mk:3: libraries/hoopl/dist- boot/build/.depend-v.haskell: No such file or directory libraries/hoopl/ghc.mk:3: libraries/hoopl/dist-boot/build/.depend-v.c_asm: No such file or directory libraries/transformers/ghc.mk:3: libraries/transformers/dist- boot/build/.depend-v.haskell: No such file or directory libraries/transformers/ghc.mk:3: libraries/transformers/dist- boot/build/.depend-v.c_asm: No such file or directory libraries/terminfo/ghc.mk:3: libraries/terminfo/dist- boot/build/.depend-v.haskell: No such file or directory libraries/terminfo/ghc.mk:3: libraries/terminfo/dist- boot/build/.depend-v.c_asm: No such file or directory libraries/ghci/ghc.mk:3: libraries/ghci/dist-boot/build/.depend-v.haskell: No such file or directory libraries/ghci/ghc.mk:3: libraries/ghci/dist-boot/build/.depend-v.c_asm: No such file or directory compiler/ghc.mk:592: compiler/stage1/build/.depend-v.haskell: No such file or directory utils/ghc-pkg/ghc.mk:70: utils/ghc-pkg/dist/build/.depend.haskell: No such file or directory "rm" -f compiler/stage1/ghc_boot_platform.h Creating compiler/stage1/ghc_boot_platform.h... Done. "rm" -f ghc/stage1/build/.depend.haskell.tmp "/usr/local/bin/ghc" -M -static -H32m -O -Wall -package-db libraries/bootstrapping.conf -hide-all-packages -i -ighc/. -ighc/stage1/build -Ighc/stage1/build -ighc/stage1/build/ghc/autogen -Ighc/stage1/build/ghc/autogen -optP-include -optPghc/stage1/build/ghc/autogen/cabal_macros.h -package-id base-4.9.1.0 -package-id array-0.5.1.1 -package-id bytestring-0.10.8.1 -package-id directory-1.3.0.0 -package-id process-1.4.3.0 -package-id filepath-1.4.1.1 -package-id ghc-boot-8.3 -package-id ghc-8.3 -package-id unix-2.7.2.1 -Wall -XHaskell2010 -no-hs-main -no-user-package-db -rtsopts -odir ghc/stage1/build -hidir ghc/stage1/build -stubdir ghc/stage1/build -dep-makefile ghc/stage1/build/.depend.haskell.tmp -dep-suffix "" -include-pkg-deps ghc/./Main.hs echo "ghc_stage1_depfile_haskell_EXISTS = YES" >> ghc/stage1/build/.depend.haskell.tmp for dir in ghc/stage1/build/./; do if test ! -d $dir; then mkdir -p $dir; fi done grep -v ' : [a-zA-Z]:/' ghc/stage1/build/.depend.haskell.tmp > ghc/stage1/build/.depend.haskell.tmp2 sed -e '/hs$/ p' -e '/hs$/ s/o /hi /g' -e '/hs$/ s/:/ : %hi: %o /' -e '/hs$/ s/^/$(eval $(call hi-rule,/' -e '/hs$/ s/$/))/' -e '/hs-boot$/ p' -e '/hs-boot$/ s/o-boot /hi-boot /g' -e '/hs-boot$/ s/:/ : %hi-boot: %o-boot /' -e '/hs-boot$/ s/^/$(eval $(call hi-rule,/' -e '/hs-boot$/ s/$/))/' ghc/stage1/build/.depend.haskell.tmp2 > ghc/stage1/build/.depend.haskell "rm" -f utils/ghc-pkg/dist/build/.depend.haskell.tmp "/usr/local/bin/ghc" -M -static -H32m -O -Wall -package-db libraries/bootstrapping.conf -hide-all-packages -i -iutils/ghc-pkg/. -iutils/ghc-pkg/dist/build -Iutils/ghc-pkg/dist/build -iutils/ghc- pkg/dist/build/ghc-pkg/autogen -Iutils/ghc-pkg/dist/build/ghc-pkg/autogen -optP-DWITH_TERMINFO -optP-include -optPutils/ghc-pkg/dist/build/ghc- pkg/autogen/cabal_macros.h -package-id base-4.9.1.0 -package-id directory-1.3.0.0 -package-id process-1.4.3.0 -package-id containers-0.5.7.1 -package-id filepath-1.4.1.1 -package-id Cabal-2.0.0.0 -package-id binary-0.8.4.1 -package-id ghc-boot-8.3 -package-id bytestring-0.10.8.1 -package-id terminfo-0.4.1.0 -package-id unix-2.7.2.1 -XHaskell2010 -no-user-package-db -rtsopts -odir utils/ghc- pkg/dist/build -hidir utils/ghc-pkg/dist/build -stubdir utils/ghc- pkg/dist/build -dep-makefile utils/ghc-pkg/dist/build/.depend.haskell.tmp -dep-suffix "" -include-pkg-deps utils/ghc-pkg/./Main.hs utils/ghc- pkg/dist/build/Version.hs utils/ghc-pkg/Main.hs:1451:40: error: error: editor placeholder in source file then termText (location db) <#> termText "\n (no packages)\n" ^ 1 error generated. `clang' failed in phase `C pre-processor'. (Exit code: 1) make[1]: *** [utils/ghc-pkg/dist/build/.depend.haskell] Error 1 make: *** [all] Error 2 }}} g++ version: {{{ ╭─bollu at cantordust ~/work/ghc-all/ghc/libraries ‹2.3.1› ‹master*› ╰─$ g++ --version 2 ↵ Configured with: --prefix=/Applications/Xcode.app/Contents/Developer/usr --with-gxx-include-dir=/usr/include/c++/4.2.1 Apple LLVM version 7.3.0 (clang-703.0.31) Target: x86_64-apple-darwin15.6.0 Thread model: posix InstalledDir: /Applications/Xcode.app/Contents/Developer/Toolchains/XcodeDefault.xctoolchain/usr/bin }}} GCC version: {{{ ╭─bollu at cantordust ~/work/ghc-all/ghc/libraries ‹2.3.1› ‹master*› ╰─$ gcc --version Configured with: --prefix=/Applications/Xcode.app/Contents/Developer/usr --with-gxx-include-dir=/usr/include/c++/4.2.1 Apple LLVM version 7.3.0 (clang-703.0.31) Target: x86_64-apple-darwin15.6.0 Thread model: posix InstalledDir: /Applications/Xcode.app/Contents/Developer/Toolchains/XcodeDefault.xctoolchain/usr/bin }}} GHC version: {{{ ╭─bollu at cantordust ~/work/ghc-all/ghc/libraries ‹2.3.1› ‹master*› ╰─$ ghc --version The Glorious Glasgow Haskell Compilation System, version 8.0.2 }}} -- -- Ticket URL: GHC The Glasgow Haskell Compiler