From ghc-devs at haskell.org Fri Jul 1 04:07:43 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 01 Jul 2016 04:07:43 -0000 Subject: [GHC] #12354: Word foldl' isn't optimized as well as Int foldl' Message-ID: <045.bac6bcbeca1cabd22823ab5f537d5cc8@haskell.org> #12354: Word foldl' isn't optimized as well as Int foldl' -------------------------------------+------------------------------------- Reporter: kjslag | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 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: -------------------------------------+------------------------------------- {{{#!hs import Data.List test :: Int -> Int test n = foldl' (+) 0 [1..n] main :: IO () main = do print $ test $ 10^8 }}} GHC optimizes the above code to the point that the garbage collector doesn't even have to do anything: {{{ $ ghc -rtsopts -O2 testInt && ./testInt +RTS -s [1 of 1] Compiling Main ( testInt.hs, testInt.o ) Linking testInt ... 5000000050000000 51,752 bytes allocated in the heap 3,480 bytes copied during GC 44,384 bytes maximum residency (1 sample(s)) 17,056 bytes maximum slop 1 MB total memory in use (0 MB lost due to fragmentation) Tot time (elapsed) Avg pause Max pause Gen 0 0 colls, 0 par 0.000s 0.000s 0.0000s 0.0000s Gen 1 1 colls, 0 par 0.000s 0.000s 0.0001s 0.0001s INIT time 0.000s ( 0.000s elapsed) MUT time 0.101s ( 0.101s elapsed) GC time 0.000s ( 0.000s elapsed) EXIT time 0.000s ( 0.000s elapsed) Total time 0.103s ( 0.102s elapsed) %GC time 0.1% (0.1% elapsed) Alloc rate 511,162 bytes per MUT second Productivity 99.8% of total user, 100.9% of total elapsed }}} However, if I change the type of {{{test}}} to {{{test :: Word -> Word}}}, then a lot of garbage is produced and the code runs 40x slower: {{{ ghc -rtsopts -O2 testWord && ./testWord +RTS -s [1 of 1] Compiling Main ( testWord.hs, testWord.o ) Linking testWord ... 5000000050000000 11,200,051,784 bytes allocated in the heap 1,055,520 bytes copied during GC 44,384 bytes maximum residency (2 sample(s)) 21,152 bytes maximum slop 1 MB total memory in use (0 MB lost due to fragmentation) Tot time (elapsed) Avg pause Max pause Gen 0 21700 colls, 0 par 0.077s 0.073s 0.0000s 0.0000s Gen 1 2 colls, 0 par 0.000s 0.000s 0.0001s 0.0001s INIT time 0.000s ( 0.000s elapsed) MUT time 4.551s ( 4.556s elapsed) GC time 0.077s ( 0.073s elapsed) EXIT time 0.000s ( 0.000s elapsed) Total time 4.630s ( 4.630s elapsed) %GC time 1.7% (1.6% elapsed) Alloc rate 2,460,957,186 bytes per MUT second Productivity 98.3% of total user, 98.3% of total elapsed }}} I expected the performance to be nearly identical. I'm using GHC version 8.0.1 on x86_64 Arch Linux. I asked about this on stackoverflow, and the issue appears to be related to rewrite rules: [http://stackoverflow.com/a/38113639/6531137] -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 1 07:02:45 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 01 Jul 2016 07:02:45 -0000 Subject: [GHC] #12128: ghci cause panic on 8.0.1 In-Reply-To: <043.d0d8e98d01cc863c9b0e7ff6db6baf83@haskell.org> References: <043.d0d8e98d01cc863c9b0e7ff6db6baf83@haskell.org> Message-ID: <058.31c893a82d125472a86db0a1ddf1bf2f@haskell.org> #12128: ghci cause panic on 8.0.1 -------------------------------------+------------------------------------- Reporter: zxtx | Owner: seraphime Type: bug | Status: new Priority: high | Milestone: 8.0.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 seraphime): * Attachment "empty-case-not-trivial-in-interpreted-code.patch" removed. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 1 07:02:45 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 01 Jul 2016 07:02:45 -0000 Subject: [GHC] #12128: ghci cause panic on 8.0.1 In-Reply-To: <043.d0d8e98d01cc863c9b0e7ff6db6baf83@haskell.org> References: <043.d0d8e98d01cc863c9b0e7ff6db6baf83@haskell.org> Message-ID: <058.345c486fd648eb92390ea3901fe10ffb@haskell.org> #12128: ghci cause panic on 8.0.1 -------------------------------------+------------------------------------- Reporter: zxtx | Owner: seraphime Type: bug | Status: new Priority: high | Milestone: 8.0.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 seraphime): * Attachment "empty-case-not-trivial-in-interpreted-code.patch" added. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 1 07:04:40 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 01 Jul 2016 07:04:40 -0000 Subject: [GHC] #12128: ghci cause panic on 8.0.1 In-Reply-To: <043.d0d8e98d01cc863c9b0e7ff6db6baf83@haskell.org> References: <043.d0d8e98d01cc863c9b0e7ff6db6baf83@haskell.org> Message-ID: <058.d20647b72a875bbf74602cec8ba9727f@haskell.org> #12128: ghci cause panic on 8.0.1 -------------------------------------+------------------------------------- Reporter: zxtx | Owner: seraphime Type: bug | Status: new Priority: high | Milestone: 8.0.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): Phab:D2374 Wiki Page: | -------------------------------------+------------------------------------- Changes (by seraphime): * differential: => Phab:D2374 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 1 07:46:40 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 01 Jul 2016 07:46:40 -0000 Subject: [GHC] #12354: Word foldl' isn't optimized as well as Int foldl' In-Reply-To: <045.bac6bcbeca1cabd22823ab5f537d5cc8@haskell.org> References: <045.bac6bcbeca1cabd22823ab5f537d5cc8@haskell.org> Message-ID: <060.b40eb8d4adc550f5fe82b662937728c6@haskell.org> #12354: Word foldl' isn't optimized as well as Int foldl' -------------------------------------+------------------------------------- Reporter: kjslag | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.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 nomeata): As pointed out by dfeuer on stackexchange, the `Enum` instance for `Int` is better than the one for `Word`: `Int`: {{{ instance Enum Int where {-# INLINE enumFromTo #-} enumFromTo (I# x) (I# y) = eftInt x y {-# RULES "eftInt" [~1] forall x y. eftInt x y = build (\ c n -> eftIntFB c n x y) "eftIntList" [1] eftIntFB (:) [] = eftInt #-} {- Note [How the Enum rules work] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ * Phase 2: eftInt ---> build . eftIntFB * Phase 1: inline build; eftIntFB (:) --> eftInt * Phase 0: optionally inline eftInt -} {-# NOINLINE [1] eftInt #-} eftInt :: Int# -> Int# -> [Int] -- [x1..x2] eftInt x0 y | isTrue# (x0 ># y) = [] | otherwise = go x0 where go x = I# x : if isTrue# (x ==# y) then [] else go (x +# 1#) {-# INLINE [0] eftIntFB #-} eftIntFB :: (Int -> r -> r) -> r -> Int# -> Int# -> r eftIntFB c n x0 y | isTrue# (x0 ># y) = n | otherwise = go x0 where go x = I# x `c` if isTrue# (x ==# y) then n else go (x +# 1#) -- Watch out for y=maxBound; hence ==, not > -- Be very careful not to have more than one "c" -- so that when eftInfFB is inlined we can inline -- whatever is bound to "c" }}} Now `Word` actually uses the implementation for `Integer` {{{ enumFromTo n1 n2 = map integerToWordX [wordToIntegerX n1 .. wordToIntegerX n2] }}} which uses {{{ instance Enum Integer where enumFromTo x lim = enumDeltaToInteger x 1 lim }}} Now `enumDeltaToInteger` has rewrite rules set up, but it turns out that `Word`’s `enumFromTo` is never inlined, so this setup has no chance of fusing here. Inlining this function into my test code causes `fold/build` to fire, cutting down allocation severely, but the conversion from and to `Integer` remains. One could of course write similar hand-written code such as for `Int` also for `Word`. But what about `Word8`, `Word16`, `Word32` and `Word64` then? Where does it stop? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 1 08:31:19 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 01 Jul 2016 08:31:19 -0000 Subject: [GHC] #12355: Invalid assembly in foreign prim Message-ID: <043.e628067e14a84102326ba14e6b406a11@haskell.org> #12355: Invalid assembly in foreign prim -------------------------------------+------------------------------------- Reporter: osa1 | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.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: -------------------------------------+------------------------------------- {{{ ➜ prim_panic ghc Lib.hs [1 of 1] Compiling Lib ( Lib.hs, Lib.o ) /tmp/ghc14440_0/ghc_2.s: Assembler messages: /tmp/ghc14440_0/ghc_2.s:65:0: error: Error: number of operands mismatch for `jmp' `gcc' failed in phase `Assembler'. (Exit code: 1) ➜ prim_panic cat Lib.hs {-# LANGUAGE GHCForeignImportPrim, UnliftedFFITypes, MagicHash #-} module Lib where import GHC.Prim foreign import prim f1 :: Int# -> Int# }}} Tried with: HEAD as of today, 8.0.1. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 1 09:17:08 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 01 Jul 2016 09:17:08 -0000 Subject: [GHC] #12343: base/tests/topHandler03.run failures In-Reply-To: <046.b79cb68f075678e2e8a51f3677b63ae6@haskell.org> References: <046.b79cb68f075678e2e8a51f3677b63ae6@haskell.org> Message-ID: <061.f8f5180f64b6ef1a056e6297b823ffbd@haskell.org> #12343: base/tests/topHandler03.run failures -------------------------------------+------------------------------------- Reporter: niteria | Owner: thomie Type: bug | Status: new Priority: normal | Milestone: Component: Test Suite | 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 Thomas Miedema ): In [changeset:"0afc41b49e0ad227750421e5e2887ac9607c40fa/ghc" 0afc41b/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="0afc41b49e0ad227750421e5e2887ac9607c40fa" Testsuite: be less strict about topHandler03's stderr Fixes #12343. }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 1 09:18:07 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 01 Jul 2016 09:18:07 -0000 Subject: [GHC] #12343: base/tests/topHandler03.run failures In-Reply-To: <046.b79cb68f075678e2e8a51f3677b63ae6@haskell.org> References: <046.b79cb68f075678e2e8a51f3677b63ae6@haskell.org> Message-ID: <061.357a797e425f2360c578259a439028ae@haskell.org> #12343: base/tests/topHandler03.run failures -------------------------------------+------------------------------------- Reporter: niteria | Owner: thomie Type: bug | Status: closed Priority: normal | Milestone: 8.2.1 Component: Test Suite | 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): Wiki Page: | -------------------------------------+------------------------------------- Changes (by thomie): * status: new => closed * resolution: => fixed * milestone: => 8.2.1 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 1 10:28:58 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 01 Jul 2016 10:28:58 -0000 Subject: [GHC] #12354: Word foldl' isn't optimized as well as Int foldl' In-Reply-To: <045.bac6bcbeca1cabd22823ab5f537d5cc8@haskell.org> References: <045.bac6bcbeca1cabd22823ab5f537d5cc8@haskell.org> Message-ID: <060.d0deae7dde5cf8520f4dc3b9d11c447d@haskell.org> #12354: Word foldl' isn't optimized as well as Int foldl' -------------------------------------+------------------------------------- Reporter: kjslag | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.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 simonpj): > it turns out that Word’s enumFromTo is never inlined, so this setup has no chance of fusing here So the short term solution is to add an INLINE for Word's `enumFromTo`? > Where does it stop? Well you might hope that you could write `eftInt`, `eftIntFB` once, at type `a` and SPECIALISE them. That would save copying them manually. Writing rewrite rules that also specialise is something I have not thought much about though. I suppose that, conceivably, all the fusion could happen generically (i.e. on the class-overloaded functions), before we specialise to the particular type. To achieve that, we'd have to delay the class-op selection e.g. `eunmFrom dEnumInt` --> `enumFrom_Int`. But that ought to be possible. A good project here. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 1 10:29:34 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 01 Jul 2016 10:29:34 -0000 Subject: [GHC] #12354: Word foldl' isn't optimized as well as Int foldl' In-Reply-To: <045.bac6bcbeca1cabd22823ab5f537d5cc8@haskell.org> References: <045.bac6bcbeca1cabd22823ab5f537d5cc8@haskell.org> Message-ID: <060.1f9f35dc9ab925644d5930a73964aaf3@haskell.org> #12354: Word foldl' isn't optimized as well as Int foldl' -------------------------------------+------------------------------------- Reporter: kjslag | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.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 bgamari): I think it's reasonable to expect that `Word` and `Int` optimize roughly as well. I might even go so far to say that the same should be expected of the narrower `Word` and `Int` variants. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 1 11:10:37 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 01 Jul 2016 11:10:37 -0000 Subject: [GHC] #12354: Word foldl' isn't optimized as well as Int foldl' In-Reply-To: <045.bac6bcbeca1cabd22823ab5f537d5cc8@haskell.org> References: <045.bac6bcbeca1cabd22823ab5f537d5cc8@haskell.org> Message-ID: <060.c81b39301039843f3b9396a135662982@haskell.org> #12354: Word foldl' isn't optimized as well as Int foldl' -------------------------------------+------------------------------------- Reporter: kjslag | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.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 bgamari): > Well you might hope that you could write `eftInt`, `eftIntFB` once, at type `a` and SPECIALISE them. That would save copying them manually. Indeed, unfortunately this would require that `eftInt` be runtime- representationally polymorphic since `Word :: RuntimeRep WordRep` and `Int :: RuntimeRep IntRep`. This is a rather unfortunate limitation since we would like to ensure that the polymorphism is resolved at compile-time via inlining. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 1 11:12:42 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 01 Jul 2016 11:12:42 -0000 Subject: [GHC] #12354: Word foldl' isn't optimized as well as Int foldl' In-Reply-To: <045.bac6bcbeca1cabd22823ab5f537d5cc8@haskell.org> References: <045.bac6bcbeca1cabd22823ab5f537d5cc8@haskell.org> Message-ID: <060.20f0a552584427e0639b04a9312cef39@haskell.org> #12354: Word foldl' isn't optimized as well as Int foldl' -------------------------------------+------------------------------------- Reporter: kjslag | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.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 simonpj): I think the generic versions could work with boxed values and we could fuse there. After fusion the unboxed versions could kick in. Short term: just replicate Int stuff for Word. Medium term: let's hope someone takes up the challenge. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 1 11:24:58 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 01 Jul 2016 11:24:58 -0000 Subject: [GHC] #12354: Word foldl' isn't optimized as well as Int foldl' In-Reply-To: <045.bac6bcbeca1cabd22823ab5f537d5cc8@haskell.org> References: <045.bac6bcbeca1cabd22823ab5f537d5cc8@haskell.org> Message-ID: <060.64e5d0648ff44de4cabc414d315d4fe2@haskell.org> #12354: Word foldl' isn't optimized as well as Int foldl' -------------------------------------+------------------------------------- Reporter: kjslag | Owner: Type: bug | Status: patch Priority: normal | Milestone: Component: Compiler | Version: 8.0.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): Phab:D2376 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => patch * differential: => Phab:D2376 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 1 11:28:15 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 01 Jul 2016 11:28:15 -0000 Subject: [GHC] #12239: Dependent type family does not reduce In-Reply-To: <048.080c799bf1728edbd965cda3e26adbaf@haskell.org> References: <048.080c799bf1728edbd965cda3e26adbaf@haskell.org> Message-ID: <063.0c50842b68e5d923e4becb4c790f7a7b@haskell.org> #12239: Dependent type family does not reduce -------------------------------------+------------------------------------- Reporter: int-index | Owner: goldfire Type: bug | Status: new Priority: normal | Milestone: 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: | -------------------------------------+------------------------------------- Comment (by simonpj): > I was wondering if someone would find a way to tickle this I don't understand what you mean, Richard. The code in the Description *does* tickle it, no? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 1 11:31:59 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 01 Jul 2016 11:31:59 -0000 Subject: [GHC] #12249: Template Haskell top level scoping error In-Reply-To: <046.2c212e8451a2f7a23ceaf92c7fd020ab@haskell.org> References: <046.2c212e8451a2f7a23ceaf92c7fd020ab@haskell.org> Message-ID: <061.30a9fddbfcddd2e50bdac46fa218878c@haskell.org> #12249: Template Haskell top level scoping error -------------------------------------+------------------------------------- Reporter: simonpj | Owner: 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 simonpj): > But why do we want this behavior? Consider the code in the Description. It seems perfectly reasonable to me; the two quasiquotes both bind 'x' but in each case it's clear what binds the occurrence of `x` on the RHS of `f1`, `f2`. I'm thinking of splices that generate a wad of code that needs some auxiliary bindings; we don't want to have to worry about a clash if we happen to re-use the same name when generating the auxiliary bindings in a different splice. For example, `deriving` code. In fact it's this that is causing #12245, although that code is generated by GHC itself, not by TH, but it's the same idea. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 1 11:33:02 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 01 Jul 2016 11:33:02 -0000 Subject: [GHC] #7679: Regression in -fregs-graph performance In-Reply-To: <047.9e26897513125de7441d596a4b30ee54@haskell.org> References: <047.9e26897513125de7441d596a4b30ee54@haskell.org> Message-ID: <062.2a052440b879bd7187221410cc67de8c@haskell.org> #7679: Regression in -fregs-graph performance -------------------------------------+------------------------------------- Reporter: simonmar | Owner: Type: bug | Status: merge Priority: low | Milestone: 8.0.2 Component: Compiler (NCG) | Version: 7.6.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: #7192, #8657 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => merge * milestone: => 8.0.2 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 1 11:33:29 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 01 Jul 2016 11:33:29 -0000 Subject: [GHC] #12194: ghc-pkg, package database path containing a trailing slash, and ${pkgroot} In-Reply-To: <047.2cca590f8c35da860a7f7b15269f9a76@haskell.org> References: <047.2cca590f8c35da860a7f7b15269f9a76@haskell.org> Message-ID: <062.38284e957e45858ac53ccf81512e7c36@haskell.org> #12194: ghc-pkg, package database path containing a trailing slash, and ${pkgroot} -------------------------------------+------------------------------------- Reporter: dudebout | Owner: Type: bug | Status: merge Priority: normal | Milestone: 8.0.2 Component: ghc-pkg | Version: 8.0.1 Resolution: | Keywords: pkgroot Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2336 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => merge * milestone: => 8.0.2 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 1 11:34:11 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 01 Jul 2016 11:34:11 -0000 Subject: [GHC] #11554: Self quantification in GADT data declarations In-Reply-To: <046.bec85a0842a04f6c9921baff0e29a2a1@haskell.org> References: <046.bec85a0842a04f6c9921baff0e29a2a1@haskell.org> Message-ID: <061.55073d74826105562b84cb5b20f3dfd9@haskell.org> #11554: Self quantification in GADT data declarations -------------------------------------+------------------------------------- Reporter: Rafbill | Owner: Type: bug | Status: merge Priority: high | Milestone: 8.0.2 Component: Compiler (Type | Version: 8.0.1-rc2 checker) | Resolution: | Keywords: TypeInType Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => merge -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 1 11:40:11 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 01 Jul 2016 11:40:11 -0000 Subject: [GHC] #12355: Invalid assembly in foreign prim In-Reply-To: <043.e628067e14a84102326ba14e6b406a11@haskell.org> References: <043.e628067e14a84102326ba14e6b406a11@haskell.org> Message-ID: <058.e6170f279267ff2298743e135bb56441@haskell.org> #12355: Invalid assembly in foreign prim -------------------------------------+------------------------------------- Reporter: osa1 | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | 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 bgamari): I've proposed to add this example to the testsuite in Phab:D2377. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 1 11:41:18 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 01 Jul 2016 11:41:18 -0000 Subject: [GHC] #11165: Testsuite framework failures are too easy to ignore and too hard to find In-Reply-To: <046.b1d93186c62e1a3de1b9e3c053f1008e@haskell.org> References: <046.b1d93186c62e1a3de1b9e3c053f1008e@haskell.org> Message-ID: <061.5561e7529d1ea21ec199ccd1b90ffdd0@haskell.org> #11165: Testsuite framework failures are too easy to ignore and too hard to find -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: bug | Status: closed Priority: normal | Milestone: 8.2.1 Component: Test Suite | Version: 7.10.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:D2026 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: patch => closed * resolution: => fixed * milestone: => 8.2.1 Comment: I think it is safe to call this fixed. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 1 11:46:30 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 01 Jul 2016 11:46:30 -0000 Subject: [GHC] #12128: ghci cause panic on 8.0.1 In-Reply-To: <043.d0d8e98d01cc863c9b0e7ff6db6baf83@haskell.org> References: <043.d0d8e98d01cc863c9b0e7ff6db6baf83@haskell.org> Message-ID: <058.13c270c58d6c270ab63b0b5de827fec3@haskell.org> #12128: ghci cause panic on 8.0.1 -------------------------------------+------------------------------------- Reporter: zxtx | Owner: seraphime Type: bug | Status: patch Priority: high | Milestone: 8.0.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): Phab:D2374 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => patch -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 1 11:48:06 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 01 Jul 2016 11:48:06 -0000 Subject: [GHC] #12233: Compilation does not stop on XeTeX error In-Reply-To: <046.1aef830ae49551649a9a5884d61da6ec@haskell.org> References: <046.1aef830ae49551649a9a5884d61da6ec@haskell.org> Message-ID: <061.399e539ce35c1d131b2c47d4e2aa106d@haskell.org> #12233: Compilation does not stop on XeTeX error -------------------------------------+------------------------------------- Reporter: markusr | Owner: Type: bug | Status: merge Priority: normal | Milestone: 8.0.2 Component: Build System | Version: 8.0.1 Resolution: | 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: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: patch => merge * milestone: => 8.0.2 Comment: Thanks markusr! I'll go ahead and merge this. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 1 12:03:02 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 01 Jul 2016 12:03:02 -0000 Subject: [GHC] #12356: StaticPointers support in GHCi Message-ID: <046.4add1b1a872a2608a03a4c2efa3faa77@haskell.org> #12356: StaticPointers support in GHCi -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: feature | Status: new request | 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: #12000 Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- Currently GHCi does not support `-XStaticPointers`, which is quite annoying for those of us who actually use `-XStaticPointers` in day-to-day development. It would be great if GHCi could grow support for this extension. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 1 12:03:56 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 01 Jul 2016 12:03:56 -0000 Subject: [GHC] #12000: static pointer in ghci In-Reply-To: <051.df0580fca8642cac87b47bf4dfa5d3de@haskell.org> References: <051.df0580fca8642cac87b47bf4dfa5d3de@haskell.org> Message-ID: <066.a0dccee982519f1e87adc6207688222f@haskell.org> #12000: static pointer in ghci -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: feature request | Status: closed Priority: normal | Milestone: Component: Documentation | Version: 8.1 Resolution: invalid | Keywords: | StaticPointers Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #9878 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): That being said, I would really like for GHCi to properly support `StaticPointers` since I use this extension rather often in my recent day- to-day work. I've opened #12356 to track this. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 1 12:05:33 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 01 Jul 2016 12:05:33 -0000 Subject: [GHC] #12356: StaticPointers support in GHCi In-Reply-To: <046.4add1b1a872a2608a03a4c2efa3faa77@haskell.org> References: <046.4add1b1a872a2608a03a4c2efa3faa77@haskell.org> Message-ID: <061.b91b9abb4c4418531693d6aa70a40b96@haskell.org> #12356: StaticPointers support in GHCi -------------------------------------+------------------------------------- Reporter: bgamari | Owner: 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 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): there are a few notes on the current state of things on [[https://ghc.haskell.org/trac/ghc/wiki/StaticPointers/Old#InGHCi|StaticPointers/Old]] and #12000. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 1 12:06:18 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 01 Jul 2016 12:06:18 -0000 Subject: [GHC] #12356: StaticPointers support in GHCi In-Reply-To: <046.4add1b1a872a2608a03a4c2efa3faa77@haskell.org> References: <046.4add1b1a872a2608a03a4c2efa3faa77@haskell.org> Message-ID: <061.fd01e56788d0ad7541c2e2a21a6339dd@haskell.org> #12356: StaticPointers support in GHCi -------------------------------------+------------------------------------- Reporter: bgamari | Owner: 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 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * cc: facundo.dominguez (added) Comment: Facundo, do you suppose you could describe what is currently missing to get proper `StaticPointers` support in GHCi? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 1 12:07:19 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 01 Jul 2016 12:07:19 -0000 Subject: [GHC] #12355: Invalid assembly in foreign prim In-Reply-To: <043.e628067e14a84102326ba14e6b406a11@haskell.org> References: <043.e628067e14a84102326ba14e6b406a11@haskell.org> Message-ID: <058.9fccb12fad268a859e92253c2d078c0e@haskell.org> #12355: Invalid assembly in foreign prim -------------------------------------+------------------------------------- Reporter: osa1 | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | 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 simonpj): Does anyone know what the problem actually is here? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 1 12:19:41 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 01 Jul 2016 12:19:41 -0000 Subject: [GHC] #12233: Compilation does not stop on XeTeX error In-Reply-To: <046.1aef830ae49551649a9a5884d61da6ec@haskell.org> References: <046.1aef830ae49551649a9a5884d61da6ec@haskell.org> Message-ID: <061.370d87554612d8ba0a70a6fab8cd4225@haskell.org> #12233: Compilation does not stop on XeTeX error -------------------------------------+------------------------------------- Reporter: markusr | Owner: Type: bug | Status: closed Priority: normal | Milestone: 8.0.2 Component: Build System | Version: 8.0.1 Resolution: fixed | 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: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: merge => closed * resolution: => fixed -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 1 12:21:23 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 01 Jul 2016 12:21:23 -0000 Subject: [GHC] #11727: Allow one type signature for multiple pattern synonyms In-Reply-To: <049.0fba9aba358ebb714117eb166e00090c@haskell.org> References: <049.0fba9aba358ebb714117eb166e00090c@haskell.org> Message-ID: <064.1b6f32aa2f846c923ba1921a57a6c1b4@haskell.org> #11727: Allow one type signature for multiple pattern synonyms -------------------------------------+------------------------------------- Reporter: mpickering | Owner: mpickering Type: feature request | Status: closed Priority: normal | Milestone: 8.2.1 Component: Compiler | Version: 7.10.3 Resolution: fixed | Keywords: | PatternSynonyms Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | patsyn/should_compile/T11727 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2083 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => closed * resolution: => fixed @@ -6,1 +6,1 @@ - {{{ + {{{#!hs New description: There's no reason why we shouldn't allow the same type signature for multiple pattern synonyms just like ordinary functions. For example, {{{#!hs pattern A,B,C,D :: Int pattern A = 5 pattern B = 6 pattern C = 7 pattern D = 8 }}} -- -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 1 12:22:19 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 01 Jul 2016 12:22:19 -0000 Subject: [GHC] #12230: Non-deterministic ghc-iserv terminated error In-Reply-To: <045.b7f373deda89bbecf4c896a589c74e49@haskell.org> References: <045.b7f373deda89bbecf4c896a589c74e49@haskell.org> Message-ID: <060.119d17ab6a6988ec2588735d3816204a@haskell.org> #12230: Non-deterministic ghc-iserv terminated error -------------------------------------+------------------------------------- Reporter: ezyang | Owner: simonmar Type: bug | Status: new Priority: highest | Milestone: 8.2.1 Component: GHCi | 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): Phab:D2371 Wiki Page: | -------------------------------------+------------------------------------- Comment (by Simon Marlow ): In [changeset:"ee8d1facb20ab579c44bf4cd7d5fd807d547b6ad/ghc" ee8d1fa/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="ee8d1facb20ab579c44bf4cd7d5fd807d547b6ad" Remove unused oc->isImportLib (#12230) Summary: This field is never set, but it was being tested and used to decide whether to resolve an object or not. This caused non-deterministic crashes when using the RTS linker (see #12230). I suspect this is not the correct fix, but putting it up so that Phyx can tell us what the right fix should be. Test Plan: validate Reviewers: austin, Phyx, bgamari, erikd Subscribers: erikd, thomie, ezyang Differential Revision: https://phabricator.haskell.org/D2371 GHC Trac Issues: #12230 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 1 12:23:01 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 01 Jul 2016 12:23:01 -0000 Subject: [GHC] #12230: Non-deterministic ghc-iserv terminated error In-Reply-To: <045.b7f373deda89bbecf4c896a589c74e49@haskell.org> References: <045.b7f373deda89bbecf4c896a589c74e49@haskell.org> Message-ID: <060.b0c89711f8ea12b07fb3fadd97b428b6@haskell.org> #12230: Non-deterministic ghc-iserv terminated error -------------------------------------+------------------------------------- Reporter: ezyang | Owner: simonmar Type: bug | Status: closed Priority: highest | Milestone: 8.2.1 Component: GHCi | Version: 8.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:D2371 Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonmar): * status: new => closed * resolution: => fixed -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 1 13:08:23 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 01 Jul 2016 13:08:23 -0000 Subject: [GHC] #12239: Dependent type family does not reduce In-Reply-To: <048.080c799bf1728edbd965cda3e26adbaf@haskell.org> References: <048.080c799bf1728edbd965cda3e26adbaf@haskell.org> Message-ID: <063.a3cfe9bbdc7d18b4c863b2575ab96563@haskell.org> #12239: Dependent type family does not reduce -------------------------------------+------------------------------------- Reporter: int-index | Owner: goldfire Type: bug | Status: new Priority: normal | Milestone: 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: | -------------------------------------+------------------------------------- Comment (by goldfire): Yes, that's what I meant. Perhaps it would have been clearer if I said "I ''was'' wondering...". -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 1 13:17:21 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 01 Jul 2016 13:17:21 -0000 Subject: [GHC] #12249: Template Haskell top level scoping error In-Reply-To: <046.2c212e8451a2f7a23ceaf92c7fd020ab@haskell.org> References: <046.2c212e8451a2f7a23ceaf92c7fd020ab@haskell.org> Message-ID: <061.7196e77e95de5be372ea9b5446659288@haskell.org> #12249: Template Haskell top level scoping error -------------------------------------+------------------------------------- Reporter: simonpj | Owner: 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 goldfire): Hm. I suppose I've run into the same issue when writing `singletons`. But isn't this what `newName` is for? Currently, `newName` doesn't always do a good enough job at creating a top-level name that's fresh even between splices, but I'm sure we could fix it. In effect, you're trying to turn TH into a module/namespace system, where some apparently-top-level declarations actually have a limited scope. Whether or not a definition is local or global depends on the entire file, instead of being listed in one spot. While what you propose may be readily implementable, I would say that it may be time better spent designing a proper module/namespace system that TH could use. As you've designed this feature, I could see people (perhaps even including myself) using TH only for your new module-like capabilities. For example, when writing papers, I often use the same variable names in different examples. When I extract my code and compile the papers, these overlapping variable names cause annoyance. If you implement your feature, then I would put some TH dingbats in my extraction engine to avoid the ambiguous variable uses/redefinitions... but this is abusive of TH. Clearly, compiling academic papers is not the primary use-case for Haskell (or is it? I suppose it once was!) but I'm sure I'm not the only one who would do such shenanigans. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 1 15:22:07 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 01 Jul 2016 15:22:07 -0000 Subject: [GHC] #4012: Compilation results are not deterministic In-Reply-To: <043.9c3dc141e8901acb12e4d7c1e6038096@haskell.org> References: <043.9c3dc141e8901acb12e4d7c1e6038096@haskell.org> Message-ID: <058.c04586b127fed298d03fe21a25877048@haskell.org> #4012: Compilation results are not deterministic -------------------------------------+------------------------------------- Reporter: kili | Owner: niteria Type: bug | Status: new Priority: high | Milestone: 8.2.1 Component: Compiler | Version: 6.12.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Other | Test Case: Blocked By: 11362 | Blocking: 12262 Related Tickets: #10424 | Differential Rev(s): Phab:D910, | Phab:D1073, Phab:D1133, Phab:D1192, | Phab:D1268, Phab:D1360, Phab:D1373, Wiki Page: | Phab:D1396, Phab:D1457, Phab:D1468, DeterministicBuilds | Phab:D1487, Phab:D1504, Phab:D1508 -------------------------------------+------------------------------------- Comment (by Bartosz Nitka ): In [changeset:"0ab63cf48580abbfe15ece934aec093203f29ed2/ghc" 0ab63cf/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="0ab63cf48580abbfe15ece934aec093203f29ed2" Kill varEnvElts in seqDmdEnv GHC Trac: #4012 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 1 16:10:49 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 01 Jul 2016 16:10:49 -0000 Subject: [GHC] #12355: Invalid assembly in foreign prim In-Reply-To: <043.e628067e14a84102326ba14e6b406a11@haskell.org> References: <043.e628067e14a84102326ba14e6b406a11@haskell.org> Message-ID: <058.0d10b69e26266904f6dee95d7c9298a1@haskell.org> #12355: Invalid assembly in foreign prim -------------------------------------+------------------------------------- Reporter: osa1 | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | 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 bgamari): Something is indeed quite fishy. The C-- for this code is as follows, {{{ [section ""data" . Lib.f1_closure" { Lib.f1_closure: const Lib.f1_info; }, Lib.f1_entry() // [R2] { info_tbl: [(cG7, label: Lib.f1_info rep:HeapRep static { Fun {arity: 1 fun_type: ArgSpec 4} })] stack_info: arg_space: 8 updfr_space: Just 8 } {offset cG7: _B1::I64 = R2; goto cG9; cG9: R1 = _B1::I64; call (R1) args: 8, res: 0, upd: 8; } }] }}} It looks like the target is being pretty-printed as `mempty`. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 1 18:32:22 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 01 Jul 2016 18:32:22 -0000 Subject: [GHC] #11153: building lens-4.12.3 impossible happened: dupe _hs_primitive_memcpy In-Reply-To: <045.b8eb2c07dd94bd4b761d87f0dd3ec4bc@haskell.org> References: <045.b8eb2c07dd94bd4b761d87f0dd3ec4bc@haskell.org> Message-ID: <060.41458972ac07484848ad9b862ef6f143@haskell.org> #11153: building lens-4.12.3 impossible happened: dupe _hs_primitive_memcpy --------------------------------------+---------------------------------- Reporter: blippy | Owner: Type: bug | Status: infoneeded Priority: normal | Milestone: Component: libraries (other) | Version: 7.10.2 Resolution: | Keywords: Operating System: Windows | Architecture: x86 Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | --------------------------------------+---------------------------------- Comment (by Phyx-): Is this still the case with `GHC 8.0.1`? Could you output the trace from that? The duplicate error message has been improved to show where both symbols come from. That should help diagnose this. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 1 19:28:23 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 01 Jul 2016 19:28:23 -0000 Subject: [GHC] #12357: Increasing maximum constraint tuple size significantly blows up compiler allocations Message-ID: <046.dd0f12e974ac3c5c9febd70397bf4138@haskell.org> #12357: Increasing maximum constraint tuple size significantly blows up compiler allocations -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 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: -------------------------------------+------------------------------------- In July 2015 (dd3080fe0263082f65bf2570f49189c277b12e28) the maximum constraint tuple size was raised from 16 to 62 to address #10451. It turns out that this change is apparently one of the larger compile-time regressions in recent GHC history. For instance, the nofib `real/fulsom/Shapes.hs` module regresses by 16% in both compiler allocations and compile time. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 1 19:28:43 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 01 Jul 2016 19:28:43 -0000 Subject: [GHC] #12357: Increasing maximum constraint tuple size significantly blows up compiler allocations In-Reply-To: <046.dd0f12e974ac3c5c9febd70397bf4138@haskell.org> References: <046.dd0f12e974ac3c5c9febd70397bf4138@haskell.org> Message-ID: <061.5e1f5dd97cb80304dd2d59a05961eb75@haskell.org> #12357: Increasing maximum constraint tuple size significantly blows up compiler allocations -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.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): Wiki Page: | -------------------------------------+------------------------------------- Description changed by bgamari: @@ -5,1 +5,1 @@ - `real/fulsom/Shapes.hs` module regresses by 16% in both compiler + `real/fulsom/Shapes.hs` module regresses by around 15% in both compiler New description: In July 2015 (dd3080fe0263082f65bf2570f49189c277b12e28) the maximum constraint tuple size was raised from 16 to 62 to address #10451. It turns out that this change is apparently one of the larger compile-time regressions in recent GHC history. For instance, the nofib `real/fulsom/Shapes.hs` module regresses by around 15% in both compiler allocations and compile time. -- -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 1 19:42:09 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 01 Jul 2016 19:42:09 -0000 Subject: [GHC] #12357: Increasing maximum constraint tuple size significantly blows up compiler allocations In-Reply-To: <046.dd0f12e974ac3c5c9febd70397bf4138@haskell.org> References: <046.dd0f12e974ac3c5c9febd70397bf4138@haskell.org> Message-ID: <061.5fd2dfe5d377e29eede4a92eeb2be7b6@haskell.org> #12357: Increasing maximum constraint tuple size significantly blows up compiler allocations -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.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): Wiki Page: | -------------------------------------+------------------------------------- Description changed by bgamari: @@ -7,0 +7,5 @@ + + Judging by ticky and the cost-center profiler the performance regression + appears to simply be the result of the loading the new declarations from + the interface file, as one might expect. Nevertheless, it's quite silly to + pay such a large price for a change that only gets occasionally exercised. New description: In July 2015 (dd3080fe0263082f65bf2570f49189c277b12e28) the maximum constraint tuple size was raised from 16 to 62 to address #10451. It turns out that this change is apparently one of the larger compile-time regressions in recent GHC history. For instance, the nofib `real/fulsom/Shapes.hs` module regresses by around 15% in both compiler allocations and compile time. Judging by ticky and the cost-center profiler the performance regression appears to simply be the result of the loading the new declarations from the interface file, as one might expect. Nevertheless, it's quite silly to pay such a large price for a change that only gets occasionally exercised. -- -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 1 19:59:26 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 01 Jul 2016 19:59:26 -0000 Subject: [GHC] #12357: Increasing maximum constraint tuple size significantly blows up compiler allocations In-Reply-To: <046.dd0f12e974ac3c5c9febd70397bf4138@haskell.org> References: <046.dd0f12e974ac3c5c9febd70397bf4138@haskell.org> Message-ID: <061.1219019c87b60a9bdca329a8fb94ceee@haskell.org> #12357: Increasing maximum constraint tuple size significantly blows up compiler allocations -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.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): Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): [[http://home.smart-cactus.org/~ben/ghc/tickets/T12357/Shapes- ticky.diff.html|Here's]] a diff of ticky output from `fulsom`'s `Shapes` module compiled with dd3080fe0263082f65bf2570f49189c277b12e28 and its parent. There's nothing particularly alarming here, as far as I can tell: most of the quantitative differences are in `IfaceType`, `Unique`, `Binary`, and `BinIface`, which all makes good sense given we now need to load more declarations from the `GHC.Classes` interface file. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 1 20:09:15 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 01 Jul 2016 20:09:15 -0000 Subject: [GHC] #12357: Increasing maximum constraint tuple size significantly blows up compiler allocations In-Reply-To: <046.dd0f12e974ac3c5c9febd70397bf4138@haskell.org> References: <046.dd0f12e974ac3c5c9febd70397bf4138@haskell.org> Message-ID: <061.42b4e645fcc3641c987bb0de8c40b7f6@haskell.org> #12357: Increasing maximum constraint tuple size significantly blows up compiler allocations -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.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): Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): One thing to point out here is that a significant amount of cost from this patch is due to the construction of the superclass dictionary selectors (e.g. `OccName.mkSuperDictSelOcc`), since we now have to construct a few thousand more selectors than we did previously. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 1 20:34:53 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 01 Jul 2016 20:34:53 -0000 Subject: [GHC] #12357: Increasing maximum constraint tuple size significantly blows up compiler allocations In-Reply-To: <046.dd0f12e974ac3c5c9febd70397bf4138@haskell.org> References: <046.dd0f12e974ac3c5c9febd70397bf4138@haskell.org> Message-ID: <061.b4ccfab481ec5bd33394b8b945e9c55f@haskell.org> #12357: Increasing maximum constraint tuple size significantly blows up compiler allocations -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.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): Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): Here are the actual relative changes in allocations. ||= % change =||= alloc A =||= alloc B =||= name =|| || +79980.0% || 320 || 256256 || `sat_sjxb (ghc-7.11.20150614:TcRnMonad)` || || +3860.0% || 440 || 17424 || `sat_sjxt (ghc-7.11.20150614:TcRnMonad)` || || +3772.0% || 400 || 15488 || `sat_sjxu (ghc-7.11.20150614:TcRnMonad)` || || +1516.7% || 432 || 6984 || `sat_sjyB (ghc-7.11.20150614:TcHsSyn)` || || +1253.1% || 22040 || 298224 || ` (ghc-7.11.20150614:OccName.mkSuperDictSelOcc)` || || +417.8% || 58488 || 302840 || `ds1 (ghc-7.11.20150614:LoadIface)` || || +307.9% || 499856 || 2038832 || `$wa3 (ghc-7.11.20150614:Encoding.)` || || +287.5% || 384 || 1488 || ` (ghc-7.11.20150614:Unique.mkCTupleTyConUnique)` || || +287.5% || 3072 || 11904 || ` (ghc-7.11.20150614:TysWiredIn.cTupleTyConName)` || || +255.6% || 936 || 3328 || `sat_sjz8 (ghc-7.11.20150614:TcRnMonad)` || || +165.7% || 4477200 || 11897920 || `$wa5 (ghc-7.11.20150614:Encoding)` || || +139.4% || 2376 || 5688 || ` (ghc-7.11.20150614:OccName.mkClassDataConOcc)` || || +132.4% || 17792 || 41344 || ` (ghc-7.11.20150614:IfaceSyn.ifaceDeclImplicitBndrs)` || || +77.3% || 39520 || 70064 || ` (ghc-7.11.20150614:FastString.mkFastString)` || || +51.0% || 337216 || 509256 || ` (ghc-7.11.20150614:IfaceEnv.lookupOrig)` || || +50.7% || 259992 || 391920 || `$wa86 (ghc-7.11.20150614:Binary)` || || +49.6% || 63104 || 94384 || `updNameCacheTcRn (ghc-7.11.20150614:IfaceEnv)` || || +48.9% || 3760 || 5600 || `$cget (ghc-7.11.20150614:CoAxiom)` || || +47.7% || 224336 || 331240 || ` (ghc-7.11.20150614:IfaceEnv.extendNameCache)` || || +45.4% || 302448 || 439896 || ` (ghc-7.11.20150614:UniqSupply.takeUniqFromSupply)` || || +44.6% || 245336 || 354816 || ` (ghc-7.11.20150614:Name.mkExternalName)` || || +43.6% || 350440 || 503160 || ` (ghc-7.11.20150614:FastString.unpackFS)` || || +42.7% || 143104 || 204192 || `$wa2 (ghc-7.11.20150614:Encoding.)` || || +28.8% || 5168 || 6656 || `sat_sjzc (ghc-7.11.20150614:TcHsSyn)` || || +28.1% || 318552 || 407976 || ` (ghc-7.11.20150614:Unique.mkVarOccUnique)` || || +27.7% || 3984 || 5088 || ` (ghc-7.11.20150614:OccName.mkDataConWorkerOcc)` || || +27.6% || 283320 || 361520 || ` (ghc-7.11.20150614:FastString.mkFastStringByteString3)` || || +27.6% || 113328 || 144608 || `$wa (ghc-7.11.20150614:Encoding.)` || || +24.2% || 4560 || 5664 || ` (ghc-7.11.20150614:OccName.mkOccName)` || || +24.2% || 905968 || 1124928 || ` (ghc-7.11.20150614:TysWiredIn.isBuiltInOcc_maybe)` || || +23.5% || 605144 || 747376 || `$wa (ghc-7.11.20150614:FastString.)` || || +23.3% || 269056 || 331616 || `sat_s29W (ghc-7.11.20150614:UniqSupply)` || || +23.3% || 269056 || 331616 || `sat_s29V (ghc-7.11.20150614:UniqSupply)` || || +23.3% || 672640 || 829040 || `sat_s29U (ghc-7.11.20150614:UniqSupply)` || || +23.3% || 134528 || 165808 || `a5 (ghc-7.11.20150614:UniqSupply)` || || +22.8% || 3274992 || 4021296 || `$ccompare1 (ghc-7.11.20150614:Module)` || -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 1 20:59:43 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 01 Jul 2016 20:59:43 -0000 Subject: [GHC] #12357: Increasing maximum constraint tuple size significantly blows up compiler allocations In-Reply-To: <046.dd0f12e974ac3c5c9febd70397bf4138@haskell.org> References: <046.dd0f12e974ac3c5c9febd70397bf4138@haskell.org> Message-ID: <061.a8ee8f4ac8f20f1b5107a61ac3d8b7e7@haskell.org> #12357: Increasing maximum constraint tuple size significantly blows up compiler allocations -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.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): Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): It's a bit surprising how much changes in `Encoding` given that the new and old interface files are identical save the new classes, the names of which aren't terribly long. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 1 21:36:05 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 01 Jul 2016 21:36:05 -0000 Subject: [GHC] #12356: StaticPointers support in GHCi In-Reply-To: <046.4add1b1a872a2608a03a4c2efa3faa77@haskell.org> References: <046.4add1b1a872a2608a03a4c2efa3faa77@haskell.org> Message-ID: <061.27d4c5d7a1f26ca83802a324088ad618@haskell.org> #12356: StaticPointers support in GHCi -------------------------------------+------------------------------------- Reporter: bgamari | Owner: 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 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by facundo.dominguez): When compiling a module, the FloatOut pass puts StaticPtrs in the top level and the tidy-core pass generates a C constructor function which inserts the top-level bindings in the static pointer table (SPT) when the module is loaded. In GHCi, I guess that bindings could be inserted in the SPT when they are linked. I don't know if the FloatOut pass is used when compiling code in GHCi, if not, floating the static pointer values to the top-level would need to be accomplished otherwise. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jul 2 06:18:08 2016 From: ghc-devs at haskell.org (GHC) Date: Sat, 02 Jul 2016 06:18:08 -0000 Subject: [GHC] #5218: Add unpackCStringLen# to create Strings from string literals In-Reply-To: <044.69091f2248f564745af8f69c26fefc28@haskell.org> References: <044.69091f2248f564745af8f69c26fefc28@haskell.org> Message-ID: <059.d5f1d420ffd2caedee8b346716f210f7@haskell.org> #5218: Add unpackCStringLen# to create Strings from string literals -------------------------------------+------------------------------------- Reporter: tibbe | Owner: thoughtpolice Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.0.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: #5877 #10064 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Mathnerd314): I have yet another proposal, namely to add low-level construction methods to `IsString`: {{{#!hs class IsString a where fromString :: String -> a -- as before fromString_asc# :: Addr# -> Int# -> a fromString_asc# a _ = fromString (unpackCString# a) fromString_utf8# :: Addr# -> Int# -> a fromString_utf8# a _ = fromString (unpackCStringUtf8# a) fromString_raw# :: Addr# -> Int# -> a fromString_raw# a i = fromString (map chr (addrToWord8List a i) }}} The `String` instance would have `fromString = id`, while the `ByteString` instance would do zero-copy construction with the length information. ASCII literals would use _asc, UTF-8 literals would use _utf8, and primitive string literals would use _raw. Then `"x"# :: ByteString` would typecheck and work as expected. The only tricky part is preserving `"x"# :: Addr#` (which would be expanded to `fromString_raw# "x"# 1# :: Addr#`). It doesn't seem like `instance IsString Addr#` would be suitable. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jul 2 13:42:14 2016 From: ghc-devs at haskell.org (GHC) Date: Sat, 02 Jul 2016 13:42:14 -0000 Subject: [GHC] #5218: Add unpackCStringLen# to create Strings from string literals In-Reply-To: <044.69091f2248f564745af8f69c26fefc28@haskell.org> References: <044.69091f2248f564745af8f69c26fefc28@haskell.org> Message-ID: <059.9b86f57ba4c6b36efa5c017105e7d976@haskell.org> #5218: Add unpackCStringLen# to create Strings from string literals -------------------------------------+------------------------------------- Reporter: tibbe | Owner: thoughtpolice Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.0.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: #5877 #10064 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by carter): It does seem like a String# style design might be the most tasteful / clean, from my fuzzy understanding -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jul 2 15:26:26 2016 From: ghc-devs at haskell.org (GHC) Date: Sat, 02 Jul 2016 15:26:26 -0000 Subject: [GHC] #12150: Compile time performance degradation on code that uses undefined/error with CallStacks In-Reply-To: <045.a0bd3502ce7a1f35f82939f7b0bb87d6@haskell.org> References: <045.a0bd3502ce7a1f35f82939f7b0bb87d6@haskell.org> Message-ID: <060.4d271d7afbfaf2eccd5d7983423895c7@haskell.org> #12150: Compile time performance degradation on code that uses undefined/error with CallStacks -------------------------------------+------------------------------------- Reporter: thomie | Owner: 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 performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by gridaphobe): Sorry to be so slow! I've finally had a chance to look at this.. First of all, I can't reproduce the actual slowdown on my laptop {{{ > python test.py tempfile = /var/folders/d0/j2pt98tx3pvcpdjghyx38c9c0000gn/T/tmpvwxkz4.hs N clauses : time (s) 10 : 0.27 20 : 0.31 40 : 0.13 80 : 0.13 160 : 0.12 320 : 0.12 640 : 0.12 1280 : 0.13 }}} though the shrinking numbers makes me concerned that there may be some strange caching going on.. Ah, indeed, if I add `-fforce-recomp` I get something closer to your result {{{ > python test.py tempfile = /var/folders/d0/j2pt98tx3pvcpdjghyx38c9c0000gn/T/tmpXChceI.hs N clauses : time (s) 10 : 0.27 20 : 0.31 40 : 0.37 80 : 0.55 160 : 0.88 320 : 1.55 640 : 3.06 1280 : 6.10 }}} Second, I took a look at the generated Core, and while the '''desugared''' Core looks correct to me, the '''simplified''' Core has had the CallStacks inlined at each callsite, which is utterly pointless. In an earlier ticket (#10844) I investigated preventing CallStacks (and string literals) from being inlined, but the results were not very impressive so the patch stalled. Looks like I should take another look at it! -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jul 2 15:28:36 2016 From: ghc-devs at haskell.org (GHC) Date: Sat, 02 Jul 2016 15:28:36 -0000 Subject: [GHC] #12150: Compile time performance degradation on code that uses undefined/error with CallStacks In-Reply-To: <045.a0bd3502ce7a1f35f82939f7b0bb87d6@haskell.org> References: <045.a0bd3502ce7a1f35f82939f7b0bb87d6@haskell.org> Message-ID: <060.888398ffe5e3876a97a3b94555db1214@haskell.org> #12150: Compile time performance degradation on code that uses undefined/error with CallStacks -------------------------------------+------------------------------------- Reporter: thomie | Owner: 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 performance bug | Test Case: Blocked By: | Blocking: Related Tickets: #10844 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by gridaphobe): * related: => #10844 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jul 2 17:01:21 2016 From: ghc-devs at haskell.org (GHC) Date: Sat, 02 Jul 2016 17:01:21 -0000 Subject: [GHC] #12358: Read1/Read2 don't have methods defined in terms of ReadPrec Message-ID: <050.f17a87cdce0c0bbe442c6db7afeec481@haskell.org> #12358: Read1/Read2 don't have methods defined in terms of ReadPrec -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: feature | Status: new request | Priority: normal | Milestone: 8.2.1 Component: | Version: 8.0.1 libraries/base | 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: -------------------------------------+------------------------------------- Original Haskell libraries mailing list discussion: https://mail.haskell.org/pipermail/libraries/2016-June/027102.html > GHC 8.0 added the [http://hackage.haskell.org/package/base-4.9.0.0/docs /Data-Functor-Classes.html Data.Functor.Classes] module to `base`, and with it the `Read1` and `Read2` typeclasses. The current definition of `Read1` is this: > > {{{#!hs > class Read1 f where > liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (f a) > liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [f a] > }}} > > There's a pretty big problem with this definition: it uses `ReadS` (a synonym for `String -> [(a, String)]`). This sort of parser is very slow (the docs even [http://hackage.haskell.org/package/base-4.9.0.0/docs/Text- ParserCombinators-ReadP.html#t:ReadS admit as such]), and moreover, the actual `Read` typeclass on which Read1 is based tries to avoid using it whenever possible. > > The `Read` typeclass has this definition currently: > > {{{#!hs > class Read a where > readsPrec :: Int -> ReadS a > readList :: ReadS [a] > readPrec :: ReadPrec a > readListPrec :: ReadPrec [a] > }}} > > Where `ReadPrec` is a much more efficient parser datatype. When deriving `Read` instances, GHC defines them in terms of `readPrec`, and gives the other methods default definitions that leverage `readPrec`. > > For the sake of consistency, I propose adding analogous methods to `Read1` and `Read2` that use the `ReadPrec` datatype. For example, here is how I would change `Read1`: > > {{{#!hs > class Read1 f where > liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (f a) > liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [f a] > liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (f a) > liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [f a] > }}} > > And similarly for `Read2`. Here is a [https://gist.github.com/RyanGlScott/7cdd11d6aa878e4229acf1a682beb1fc full gist] with a sketch of what the new `Read1`/`Read2` definitions would look like, including what the default definitions of the other methods would be. Diff coming soon. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jul 2 17:18:43 2016 From: ghc-devs at haskell.org (GHC) Date: Sat, 02 Jul 2016 17:18:43 -0000 Subject: [GHC] #12358: Read1/Read2 don't have methods defined in terms of ReadPrec In-Reply-To: <050.f17a87cdce0c0bbe442c6db7afeec481@haskell.org> References: <050.f17a87cdce0c0bbe442c6db7afeec481@haskell.org> Message-ID: <065.3d7a0c9ed763f91180adc7173d65ab76@haskell.org> #12358: Read1/Read2 don't have methods defined in terms of ReadPrec -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: feature request | Status: patch Priority: normal | Milestone: 8.2.1 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): Phab:D2379 Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * status: new => patch * differential: => Phab:D2379 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jul 2 19:49:06 2016 From: ghc-devs at haskell.org (GHC) Date: Sat, 02 Jul 2016 19:49:06 -0000 Subject: [GHC] #12359: sdfs Message-ID: <047.fb4f25b881e2c64f4e34301023721e81@haskell.org> #12359: sdfs -------------------------------------+------------------------------------- Reporter: lisa1938 | Owner: 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: -------------------------------------+------------------------------------- sadada -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jul 2 21:13:56 2016 From: ghc-devs at haskell.org (GHC) Date: Sat, 02 Jul 2016 21:13:56 -0000 Subject: [GHC] #12360: Extend support for binding implicit parameters Message-ID: <051.60aab356d30170c681e545a4ae0a0e84@haskell.org> #12360: Extend support for binding implicit parameters -------------------------------------+------------------------------------- Reporter: MichaelBurge | Owner: Type: feature | Status: new request | 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: -------------------------------------+------------------------------------- Implicit parameters can only be bound using simple let and where declarations. In this example, one would expect ?t to be bound to the result of getCurrentTime, however the program is rejected with a syntax error: {{{ {-# LANGUAGE ImplicitParams #-} import Data.Time.Clock printTime :: (?t :: UTCTime) => IO () printTime = putStrLn $ show ?t main = do ?t <- getCurrentTime printTime }}} Instead, one must first bind to a regular variable and then bind the implicit parameter to it: {{{ {-# LANGUAGE ImplicitParams #-} import Data.Time.Clock printTime :: (?t :: UTCTime) => IO () printTime = putStrLn $ show ?t main = do t <- getCurrentTime let ?t = t printTime }}} In general, it seems like any pattern binding involving implicit parameters could be rewritten as a pattern binding to ordinary variables, followed by a binding of the implicit parameters to the ordinary variables. So you could bind implicit parameters buried in variables, tuples, record fields, etc.: Sugared: {{{ {-# LANGUAGE ImplicitParams #-} data Example = Example { a :: Int, b :: Int, c :: Int } f :: (?a :: Int, ?b :: Int, ?c :: Int) => Int f = ?a + ?b + ?c main = do let x = Example 1 2 3 let (Example { a = ?a, b = ?b, c = ?c }) = x let y = f putStrLn $ show y }}} Desugared: {{{ {-# LANGUAGE ImplicitParams #-} data Example = Example { a :: Int, b :: Int, c :: Int } f :: (?a :: Int, ?b :: Int, ?c :: Int) => Int f = ?a + ?b + ?c main = do let x = Example 1 2 3 let (Example { a = a, b = b, c = c }) = x let ?a = a ?b = b ?c = c let y = f putStrLn $ show y }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jul 2 21:14:49 2016 From: ghc-devs at haskell.org (GHC) Date: Sat, 02 Jul 2016 21:14:49 -0000 Subject: [GHC] #12360: Extend support for binding implicit parameters In-Reply-To: <051.60aab356d30170c681e545a4ae0a0e84@haskell.org> References: <051.60aab356d30170c681e545a4ae0a0e84@haskell.org> Message-ID: <066.1a36964fd11e7939484f366ed781632b@haskell.org> #12360: Extend support for binding implicit parameters -------------------------------------+------------------------------------- Reporter: MichaelBurge | Owner: 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: | -------------------------------------+------------------------------------- Description changed by MichaelBurge: @@ -54,2 +54,1 @@ - let y = f - putStrLn $ show y + putStrLn $ show f @@ -73,2 +72,1 @@ - let y = f - putStrLn $ show y + putStrLn $ show f New description: Implicit parameters can only be bound using simple let and where declarations. In this example, one would expect ?t to be bound to the result of getCurrentTime, however the program is rejected with a syntax error: {{{ {-# LANGUAGE ImplicitParams #-} import Data.Time.Clock printTime :: (?t :: UTCTime) => IO () printTime = putStrLn $ show ?t main = do ?t <- getCurrentTime printTime }}} Instead, one must first bind to a regular variable and then bind the implicit parameter to it: {{{ {-# LANGUAGE ImplicitParams #-} import Data.Time.Clock printTime :: (?t :: UTCTime) => IO () printTime = putStrLn $ show ?t main = do t <- getCurrentTime let ?t = t printTime }}} In general, it seems like any pattern binding involving implicit parameters could be rewritten as a pattern binding to ordinary variables, followed by a binding of the implicit parameters to the ordinary variables. So you could bind implicit parameters buried in variables, tuples, record fields, etc.: Sugared: {{{ {-# LANGUAGE ImplicitParams #-} data Example = Example { a :: Int, b :: Int, c :: Int } f :: (?a :: Int, ?b :: Int, ?c :: Int) => Int f = ?a + ?b + ?c main = do let x = Example 1 2 3 let (Example { a = ?a, b = ?b, c = ?c }) = x putStrLn $ show f }}} Desugared: {{{ {-# LANGUAGE ImplicitParams #-} data Example = Example { a :: Int, b :: Int, c :: Int } f :: (?a :: Int, ?b :: Int, ?c :: Int) => Int f = ?a + ?b + ?c main = do let x = Example 1 2 3 let (Example { a = a, b = b, c = c }) = x let ?a = a ?b = b ?c = c putStrLn $ show f }}} -- -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Jul 3 11:11:10 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 03 Jul 2016 11:11:10 -0000 Subject: [GHC] #12360: Extend support for binding implicit parameters In-Reply-To: <051.60aab356d30170c681e545a4ae0a0e84@haskell.org> References: <051.60aab356d30170c681e545a4ae0a0e84@haskell.org> Message-ID: <066.a3ae8009cdecd7a02a5edc49957526c2@haskell.org> #12360: Extend support for binding implicit parameters -------------------------------------+------------------------------------- Reporter: MichaelBurge | Owner: 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 Iceland_jack): * cc: Iceland_jack (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Jul 3 18:02:28 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 03 Jul 2016 18:02:28 -0000 Subject: [GHC] #10352: Properly link Haskell shared libs on ELF systems In-Reply-To: <045.f54c0b53e462b1ea305eb5f3c38d7688@haskell.org> References: <045.f54c0b53e462b1ea305eb5f3c38d7688@haskell.org> Message-ID: <060.f39a4f2a6603db3766e72f58f310d77f@haskell.org> #10352: Properly link Haskell shared libs on ELF systems -------------------------------------+------------------------------------- Reporter: duncan | Owner: Type: task | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.11 (Linking) | 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 Phyx-): * cc: Phyx- (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Jul 3 18:27:49 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 03 Jul 2016 18:27:49 -0000 Subject: [GHC] #12361: Add -dppr-ribbon-cols Message-ID: <045.5c23742f643ef1d6c12d25fdca511aca@haskell.org> #12361: Add -dppr-ribbon-cols -------------------------------------+------------------------------------- Reporter: ezyang | Owner: Type: feature | Status: new request | Priority: low | Milestone: Component: Compiler | Version: 8.0.1 Keywords: easy | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- Right now, users can control the width of GHC error messages (`-dppr- ribbons-per-line`) but not the ratio of line length to ribbon length. The latter would be useful, because in some contexts a user might prefer error messages to be as densely packed as possible (ratio of 1.0). -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Jul 3 19:05:19 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 03 Jul 2016 19:05:19 -0000 Subject: [GHC] #12362: don't complain about type variable ambiguity when the expression is parametrically polymorphic Message-ID: <047.240b4b09f74e6750cf0387c8656b34b6@haskell.org> #12362: don't complain about type variable ambiguity when the expression is parametrically polymorphic -------------------------------------+------------------------------------- Reporter: rwbarton | Owner: Type: feature | Status: new request | Priority: low | Milestone: Component: Compiler | Version: 8.1 (Type checker) | 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 not sure this is really a good idea, but it did come up in practice. Consider the following rather contrived program: {{{#!hs {-# LANGUAGE TypeFamilies, RankNTypes, ScopedTypeVariables, AllowAmbiguousTypes, TypeApplications #-} module E where type family T a type instance T Int = Char type instance T String = Char type instance T Bool = () newtype FT a = FT [T a] m :: forall a. (forall x. T x -> Int) -> FT a -> [Int] m f (FT xs) = map f xs }}} GHC rejects it with the error: {{{ E.hs:14:21: error: • Couldn't match type ‘T a’ with ‘T x0’ Expected type: [T x0] Actual type: [T a] NB: ‘T’ is a type function, and may not be injective The type variable ‘x0’ is ambiguous • In the second argument of ‘map’, namely ‘xs’ In the expression: map f xs In an equation for ‘m’: m f (FT xs) = map f xs • Relevant bindings include xs :: [T a] (bound at E.hs:14:9) m :: (forall x. T x -> Int) -> FT a -> [Int] (bound at E.hs:14:1) }}} The problem seems to be that GHC doesn't know at what type to instantiate `f`, because it can't conclude from the argument of `f` being `T a` that the type parameter of `f` needs to be `x`. In fact, `T` here really is not injective, so if `a` is `Int`, `x` could just as well be `String`. However, in this case the ambiguity doesn't actually matter. If `f @Int` and `f @String` have the same type because `T Int ~ T String`, then they are actually the same value too by parametricity, because there is no class constraint on `x`. Since GHC prints a message saying that `T` is not known to be injective, it sounds like it knows about the possible solution `x0 = a`. So it could just pick it, and accept the original program. With TypeApplications I can just specify the intended value of `x` by writing {{{ m f (FT xs) = map (f @a) xs }}} which is a reasonable workaround in my real use case also. Interestingly I can't seem to achieve the same thing without TypeApplications without adding a proxy argument to `f`, which I don't much want to do. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Jul 3 19:46:06 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 03 Jul 2016 19:46:06 -0000 Subject: [GHC] #12240: Common Sense for Type Classes In-Reply-To: <050.3dcf7ad3ce6a480cdc5fe8435e755275@haskell.org> References: <050.3dcf7ad3ce6a480cdc5fe8435e755275@haskell.org> Message-ID: <065.8553a0eba6c136cb6b08bd673addec8f@haskell.org> #12240: Common Sense for Type Classes -------------------------------------+------------------------------------- Reporter: Mathnerd314 | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 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 adamgundry): * cc: adamgundry (added) Comment: This is only "common sense" if you discard the open world assumption (or accept incoherence), neither of which are particularly palatable. I don't claim to have any say in whether an implementation will or will not be accepted, but bear in mind that new features have an ongoing cost, even if guarded by language flags. Feel free to work on it if you like, but seeking wider input first might be a good idea to avoid working on something that is ultimately not merged. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Jul 3 19:50:52 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 03 Jul 2016 19:50:52 -0000 Subject: [GHC] #12243: RebindableSyntax and OverloadedLabels In-Reply-To: <048.6e564fb4c32d0e67f5680b5b6de4225b@haskell.org> References: <048.6e564fb4c32d0e67f5680b5b6de4225b@haskell.org> Message-ID: <063.85632b8decd124b4bd09238edf5529f2@haskell.org> #12243: RebindableSyntax and OverloadedLabels -------------------------------------+------------------------------------- Reporter: htebalaka | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: ORF 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 adamgundry): * cc: adamgundry (added) * keywords: => ORF Comment: I think this makes sense, although it's hard to think of use cases (perhaps something involving interpreting labels with higher-rank types?). You're right that it is simply an oversight. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Jul 3 22:26:36 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 03 Jul 2016 22:26:36 -0000 Subject: [GHC] #393: functions without implementations In-Reply-To: <047.8e9c859b4db83c0d687094f53af0d886@haskell.org> References: <047.8e9c859b4db83c0d687094f53af0d886@haskell.org> Message-ID: <062.fa9a2c3df0f929331a9ffa00b5ed6e56@haskell.org> #393: functions without implementations -------------------------------------+------------------------------------- Reporter: c_maeder | Owner: Type: feature request | Status: closed Priority: normal | Milestone: ⊥ Component: Compiler (Type | Version: None checker) | Resolution: wontfix | 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): Here is a use case: Rank-N types {{{#!hs f :: (forall a. a -> a) -> (Int, Char) -> (Int, Char) f = undefined }}} does not compile. You'd have to write {{{#!hs f :: (forall a. a -> a) -> (Int, Char) -> (Int, Char) f _ = undefined }}} It would be cool if omitting the function body worked {{{#!hs f :: (forall a. a -> a) -> (Int, Char) -> (Int, Char) }}} ---- It would also be nice if this worked in local definitions {{{#!hs g = h 'a' where h :: Char -> Int }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Jul 3 23:25:04 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 03 Jul 2016 23:25:04 -0000 Subject: [GHC] #12363: Type application for infix Message-ID: <051.833fc99ca846ecc78974bf61eb05e05f@haskell.org> #12363: Type application for infix -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: feature | Status: new request | Priority: lowest | Milestone: Component: Compiler | Version: 8.0.1 (Parser) | 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: -------------------------------------+------------------------------------- `1 + @Int 10` is a parse error, I would like it to mean the same as {{{#!hs (+) @Int 1 10 }}} Thoughts? ---- Also {{{#!hs >>> pure `foldMap` @Maybe @[_] Just 'a' "a" >>> foldMap @Maybe @[_] pure (Just 'a') "a" }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 4 00:33:17 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 04 Jul 2016 00:33:17 -0000 Subject: [GHC] #12363: Type application for infix In-Reply-To: <051.833fc99ca846ecc78974bf61eb05e05f@haskell.org> References: <051.833fc99ca846ecc78974bf61eb05e05f@haskell.org> Message-ID: <066.a922f6dc5213fc016bf03d49c60f2291@haskell.org> #12363: Type application for infix -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: 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: | -------------------------------------+------------------------------------- Comment (by goldfire): I suppose this capitalizes on the fact that things beginning with `@` can't be functions that take further parameters. But I find this quite difficult to understand, with `@`-arguments binding tighter than other arguments. -1 from me, sorry. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 4 05:14:44 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 04 Jul 2016 05:14:44 -0000 Subject: [GHC] #11385: Unify named wildcards in different type applications In-Reply-To: <051.0076b412916fb4cfc0823d8e3d44b32d@haskell.org> References: <051.0076b412916fb4cfc0823d8e3d44b32d@haskell.org> Message-ID: <066.79335b8177d2b284393cf4bc4d8c084a@haskell.org> #11385: Unify named wildcards in different type applications -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.1 checker) | Keywords: Resolution: | NamedWildCards 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 Iceland_jack): {{{#!hs -- asTypeOf :: a -> a -> a asTypeOf = const @_a @_a }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 4 07:25:57 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 04 Jul 2016 07:25:57 -0000 Subject: [GHC] #12150: Compile time performance degradation on code that uses undefined/error with CallStacks In-Reply-To: <045.a0bd3502ce7a1f35f82939f7b0bb87d6@haskell.org> References: <045.a0bd3502ce7a1f35f82939f7b0bb87d6@haskell.org> Message-ID: <060.6c260dc446b1381a86792c536d644816@haskell.org> #12150: Compile time performance degradation on code that uses undefined/error with CallStacks -------------------------------------+------------------------------------- Reporter: thomie | Owner: 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 performance bug | Test Case: Blocked By: | Blocking: Related Tickets: #10844 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): I'd be happy to advise on the inlining front, once you have a bit more info. Simon -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 4 07:29:33 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 04 Jul 2016 07:29:33 -0000 Subject: [GHC] #12358: Read1/Read2 don't have methods defined in terms of ReadPrec In-Reply-To: <050.f17a87cdce0c0bbe442c6db7afeec481@haskell.org> References: <050.f17a87cdce0c0bbe442c6db7afeec481@haskell.org> Message-ID: <065.d956b8e488231b16eb37628ba531df92@haskell.org> #12358: Read1/Read2 don't have methods defined in terms of ReadPrec -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: feature request | Status: patch Priority: normal | Milestone: 8.2.1 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): Phab:D2379 Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): Are you liaising with the Core Libraries Committee on this? I didn't even know about `Read1` and `Read2`! Simon PS: does kind polymorphism help? What about `Read3`, `Read4`...? I suppose that's another story though. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 4 07:32:11 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 04 Jul 2016 07:32:11 -0000 Subject: [GHC] #12360: Extend support for binding implicit parameters In-Reply-To: <051.60aab356d30170c681e545a4ae0a0e84@haskell.org> References: <051.60aab356d30170c681e545a4ae0a0e84@haskell.org> Message-ID: <066.916111f62ab8d7231f2ac53723c497c9@haskell.org> #12360: Extend support for binding implicit parameters -------------------------------------+------------------------------------- Reporter: MichaelBurge | Owner: 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: | -------------------------------------+------------------------------------- Comment (by simonpj): I see no technical difficulties here. The question is: how common is the situation where this feature would be useful? Simon -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 4 07:40:11 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 04 Jul 2016 07:40:11 -0000 Subject: [GHC] #12361: Add -dppr-ribbon-cols In-Reply-To: <045.5c23742f643ef1d6c12d25fdca511aca@haskell.org> References: <045.5c23742f643ef1d6c12d25fdca511aca@haskell.org> Message-ID: <060.ca92ff883248ab72aeb713e600b011d8@haskell.org> #12361: Add -dppr-ribbon-cols -------------------------------------+------------------------------------- Reporter: ezyang | Owner: Type: feature request | Status: new Priority: low | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: easy 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): OK, fine with me. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 4 07:57:53 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 04 Jul 2016 07:57:53 -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.b7df9dc0b219987af7ab8afb41192581@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 nomeata): Generally sympathetic to this change, less parenthesis are good. For lambdas it looks a bit unusual, but I think I’d quickly adjust to parsing that. Minor comment: In the wiki page you include `{-# SCC #-}` and `{-# CORE #-}`. I’d doubtful about them. I mentally parse them not as control structures, but as if they were normal functions (which happen to only work when used fully applied), and would be surprised if `f a b {-# SCC #-} d e` turn into `f a b ({-# SCC #-} d e)`. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 4 08:04:42 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 04 Jul 2016 08:04:42 -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.a4b875c74d10a1bbd24f6b2b95ff4204@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: | -------------------------------------+------------------------------------- @@ -46,0 +46,2 @@ + + Wiki page: [wiki:ArgumentDo] New description: I would like the following to be valid Haskell code: {{{#!hs main = when True do putStrLn "Hello!" }}} Instead of requiring a dollar sign before the "do". This would parse as {{{#!hs main = when True (do putStrLn "Hello!") }}} Similarly, allow lambdas in the same way {{{#!hs main = forM values \value -> print value }}} parses as {{{#!hs main = forM values (\value -> print value) }}} One possible question: does this also do the same thing for LambdaCase? I think that since people expect lambda case to just be a simple desugaring it should also work, so then {{{#!hs main = forM values \case Just x -> print x Nothing -> print y }}} parses as {{{#!hs main = forM values (\case Just x -> print x Nothing -> print y) }}} Wiki page: [wiki:ArgumentDo] -- Comment (by simonpj): Akio has made a wiki page to specify the feature: [wiki:ArgumentDo] -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 4 08:12:49 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 04 Jul 2016 08:12:49 -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.056dab7d6aff10ea1169bbef63127d99@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 akio): Replying to [comment:19 nomeata]: > Generally sympathetic to this change, less parenthesis are good. For lambdas it looks a bit unusual, but I think I’d quickly adjust to parsing that. > > Minor comment: In the wiki page you include `{-# SCC #-}` and `{-# CORE #-}`. I’d doubtful about them. I mentally parse them not as control structures, but as if they were normal functions (which happen to only work when used fully applied), and would be surprised if `f a b {-# SCC #-} d e` turn into `f a b ({-# SCC #-} d e)`. Yes, I think that makes sense. Thank you for pointing it out. I just moved `SCC` and `CORE` from the main proposal to the "Design Space" section. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 4 08:36:57 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 04 Jul 2016 08:36:57 -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.92f6cdef46eb29704bd209df283b160e@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 simonpj): I'm one of those who thinks that the fact that `f R { x = e }` means `f (R { x = e })` is a mistake :-). But I appreciate the wiki page, which makes the proposal much more concrete. If there is a reasonable level of support (which seems to be the case) I won't object. I think it's be worth an email to ghc-users to draw attention to the wiki page and invite support or other feedback. Simon -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 4 11:09:09 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 04 Jul 2016 11:09:09 -0000 Subject: [GHC] #11138: Kill the terrible LLVM Mangler In-Reply-To: <046.1671c4fce95e0eb48491b5a743b485ce@haskell.org> References: <046.1671c4fce95e0eb48491b5a743b485ce@haskell.org> Message-ID: <061.da634197bb24fee5554edb206dc27f12@haskell.org> #11138: Kill the terrible LLVM Mangler -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: task | Status: new Priority: normal | Milestone: Component: Compiler (LLVM) | Version: 7.11 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 angerman): - According to majnemer_ we might not need the avx trick in the Mangler when using `-mstackalign` (which is supposedly available in 3.9) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 4 12:33:29 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 04 Jul 2016 12:33:29 -0000 Subject: [GHC] #12364: Demand analysis for sum types Message-ID: <046.d2210fe5d78e7148b495c8c2b1cf9322@haskell.org> #12364: Demand analysis for sum types -------------------------------------+------------------------------------- Reporter: nomeata | Owner: 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: -------------------------------------+------------------------------------- While working on #10613 it crossed my mind that it might be worthwhile to expand the demand type also onto sum types. So instead of {{{ | UProd [ArgUse] -- Product }}} we would have {{{ | UData [[ArgUse]] -- Data type }}} and a function like {{{ fromMaybe :: a -> Maybe a -> b }}} would have a signature of {{{ <1*U><1*U(;1*U)> }}} which indicates that the second argument of `fromMaybe` is evaluated at most once; the first constructor of the result has no arguments, the second (separated by `;`) has one argument which is also used at most once. I could imagine that this gives a lot of useful information with parsers and other code that repeatedly retuns stuff wrapped in a `Maybe` or similar type. Now, sum types are often recursive (`[]`…), and we probably want to be smarter about recursion here. But note that this is not a new problem. If you write {{{ data Stream = Stream Int Stream Stream Stream foo (Stream 0 x y z) = 0 foo (Stream 1 x y z) = foo x foo (Stream 2 x y z) = foo y foo (Stream _ x y z) = foo z }}} you already get huge demand signatures. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 4 12:40:06 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 04 Jul 2016 12:40:06 -0000 Subject: [GHC] #12364: Demand analysis for sum types In-Reply-To: <046.d2210fe5d78e7148b495c8c2b1cf9322@haskell.org> References: <046.d2210fe5d78e7148b495c8c2b1cf9322@haskell.org> Message-ID: <061.69d00ef34c5e2f2c553898c48d86de3c@haskell.org> #12364: Demand analysis for sum types -------------------------------------+------------------------------------- Reporter: nomeata | Owner: Type: task | 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 nomeata): Or maybe simply `UData [ArgUse]` and then have a flat list of all the constructor’s arguments. Implementation detail. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 4 13:04:04 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 04 Jul 2016 13:04:04 -0000 Subject: [GHC] #12364: Demand analysis for sum types In-Reply-To: <046.d2210fe5d78e7148b495c8c2b1cf9322@haskell.org> References: <046.d2210fe5d78e7148b495c8c2b1cf9322@haskell.org> Message-ID: <061.a9d21fc77f298de08f7c2c352d53fb6c@haskell.org> #12364: Demand analysis for sum types -------------------------------------+------------------------------------- Reporter: nomeata | Owner: Type: task | 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 simonpj): * cc: osa1 (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 4 13:39:07 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 04 Jul 2016 13:39:07 -0000 Subject: [GHC] #12357: Increasing maximum constraint tuple size significantly blows up compiler allocations In-Reply-To: <046.dd0f12e974ac3c5c9febd70397bf4138@haskell.org> References: <046.dd0f12e974ac3c5c9febd70397bf4138@haskell.org> Message-ID: <061.dd225652e31e2fd33bb1bf38c5326136@haskell.org> #12357: Increasing maximum constraint tuple size significantly blows up compiler allocations -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.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): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): It'd be great to investigate this `Encoding` things. There seems to be a LOT of allocation there... but all we are doing is loading an interface file, so what encoding is there to do? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 4 13:39:40 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 04 Jul 2016 13:39:40 -0000 Subject: [GHC] #12355: Invalid assembly in foreign prim In-Reply-To: <043.e628067e14a84102326ba14e6b406a11@haskell.org> References: <043.e628067e14a84102326ba14e6b406a11@haskell.org> Message-ID: <058.b9f739a7e296e2d5d4687cb7f5c61edc@haskell.org> #12355: Invalid assembly in foreign prim -------------------------------------+------------------------------------- Reporter: osa1 | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | 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 simonpj): Fishy indeed: can you probe further? Thanks -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 4 13:44:18 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 04 Jul 2016 13:44:18 -0000 Subject: [GHC] #12249: Template Haskell top level scoping error In-Reply-To: <046.2c212e8451a2f7a23ceaf92c7fd020ab@haskell.org> References: <046.2c212e8451a2f7a23ceaf92c7fd020ab@haskell.org> Message-ID: <061.f9deb229b63f34f168248afd04b9f993@haskell.org> #12249: Template Haskell top level scoping error -------------------------------------+------------------------------------- Reporter: simonpj | Owner: 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 simonpj): > But isn't this what newName is for? Well, no. `newName` is a last resort when quasiquotation won't work. Quasiquotes are the preferred way of creating lexically scoped binders. And even `newName` will create a new name with distinct unique but the same occurrence name, which will give the same "Two top level bindings for `x`" error. I don't think I'm trying to build a new module/namespace system. In Haskell 2010, it's ok to import two different functions both called `f` provided you don't refer to `f` unqualified. It's the same here. If I mention `x` I expect a complaint about ambiguity; but if I don't I expect it to be fine. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 4 13:45:43 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 04 Jul 2016 13:45:43 -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.6fd116f5dda19ad6bd20a4acd50cb6f3@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 rwbarton): I don't think parsing `f a b {-# SCC #-} d e` as `f a b ({-# SCC #-} d e)` is even an option, really, since these pragmas must be ignorable by compilers that don't understand them. Also, I think/hope this proposal does not change the parsing of any program that currently parses, right? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 4 14:38:16 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 04 Jul 2016 14:38:16 -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.7a1626ed79112ef92d4201f1a938f5c2@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): I'm intrigued by [https://ghc.haskell.org/trac/ghc/wiki/ArgumentDo#Multipleblockarguments multiple block arguments] {{{#!hs f do x do y }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 4 15:03:43 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 04 Jul 2016 15:03:43 -0000 Subject: [GHC] #12364: Demand analysis for sum types In-Reply-To: <046.d2210fe5d78e7148b495c8c2b1cf9322@haskell.org> References: <046.d2210fe5d78e7148b495c8c2b1cf9322@haskell.org> Message-ID: <061.98e1854497b3f01462e4ceffae8e6ee1@haskell.org> #12364: Demand analysis for sum types -------------------------------------+------------------------------------- Reporter: nomeata | Owner: Type: task | 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 nomeata): Work in progress on branch wip/T12354, just a quick experiment that might be able to tell us if this is worth pursuing. But it is possibly less useful than I thought: {{{ let foo a b = ... either return Left foobar .... or return Right foobaz in ... case foo a b of Left x [Demand=1*U] -> ... ; Right y [Demand=1*U] -> }}} Because the demand analyzer is a backwards analysis, the information on the usage of `foo` does not propagate into the definition of `foo` and into `foobar` and `foobaz`. For functions returning a product, a product demand is simply assumed `[Product demands for function body]` (but even there, not with single-use information). So I doubt that this is a direction worth pursuing. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 4 15:16:42 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 04 Jul 2016 15:16:42 -0000 Subject: [GHC] #12358: Read1/Read2 don't have methods defined in terms of ReadPrec In-Reply-To: <050.f17a87cdce0c0bbe442c6db7afeec481@haskell.org> References: <050.f17a87cdce0c0bbe442c6db7afeec481@haskell.org> Message-ID: <065.a6e86e67c4e3d67ebf07abeca10398d9@haskell.org> #12358: Read1/Read2 don't have methods defined in terms of ReadPrec -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: feature request | Status: patch Priority: normal | Milestone: 8.2.1 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): Phab:D2379 Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * cc: core-libraries-committee@… (added) Comment: Sorry, I should know by now to forward the CLC on things like this, seeing as how I'm on the CLC myself :) For now, I only have the above [https://mail.haskell.org/pipermail/libraries/2016-June/027102.html mailing list discussion] as evidence that this move is supported by the community. Anyways, adding `Read1` and `Read2` was decided in #11135 (associated mailing list discussion [https://mail.haskell.org/pipermail/libraries/2015-July/026014.html here]). `Read1/2` were originally defined in `transformers`, but migrated to `base` as part of an effort to bring in `Compose`/`Sum`/`Product`/`MonadIO` (and remove things from `transformers` that aren't actually, y'know, monad transformers). Ross's original definition of `Read1/2` uses `ReadS`, since that's what the report [https://www.haskell.org/onlinereport/basic.html#sect6.3.3 dictates] the definition of `Read` should use, so that's what was migrated to `base`. It didn't occur to me at the time the problems that would pose when I began to work on [https://github.com/haskell-compat/deriving- compat/issues/3 automatic derivation] of `Read1/2` instances, since GHC's derived `Read` instances use `ReadPrec` instead of `ReadS`. This ticket just serves as a way to make the methods of `Read1/2` parallel to those of `Read`, and to eventually make deriving `Read1/2` easier. (P.S., if you're curious about whether kind polymorphism can obviate the need for multiple `Read(n)` classes, you might be interested in the discussion [https://github.com/haskell/deepseq/issues/8 here]. phadej has proposed one way to solve such a problem, although it involves some eyebrow-raising `-XTypeInType` tricks.) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 4 15:33:42 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 04 Jul 2016 15:33:42 -0000 Subject: [GHC] #12364: Demand analysis for sum types In-Reply-To: <046.d2210fe5d78e7148b495c8c2b1cf9322@haskell.org> References: <046.d2210fe5d78e7148b495c8c2b1cf9322@haskell.org> Message-ID: <061.113af005e248e5cce6902cbf67c19ec7@haskell.org> #12364: Demand analysis for sum types -------------------------------------+------------------------------------- Reporter: nomeata | Owner: Type: task | 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): Expanding demand analysis for sums will get info for {{{ f :: Maybe Int -> Int f Nothing = 3 f (Just x) = x + 1 }}} Currently if a call site looks like `f (Just (p+q))` we'll build a thunk for `p+q`. But `f` always evaluates it, so that thunk is useless; we could use call-by-value. When we have unboxed sums, we can do worker/wrapper for `f` too. In contrast, you seem to be thinking about the benefits for nested CPR perhaps, in comment:3 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 4 16:25:13 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 04 Jul 2016 16:25:13 -0000 Subject: [GHC] #12364: Demand analysis for sum types In-Reply-To: <046.d2210fe5d78e7148b495c8c2b1cf9322@haskell.org> References: <046.d2210fe5d78e7148b495c8c2b1cf9322@haskell.org> Message-ID: <061.f71b4bb14967d1e07d3099d46778f8cc@haskell.org> #12364: Demand analysis for sum types -------------------------------------+------------------------------------- Reporter: nomeata | Owner: Type: task | 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 nomeata): > Currently if a call site looks like f (Just (p+q)) we'll build a thunk for p+q. But f always evaluates it, so that thunk is useless; we could use call-by-value. Actually inlining would require strictness analysis, wouldn’t it? Extending that to sums might work, but I was looking into demand analysis right now. There, we would be able to turn the thunk into a non-updateable one. I’m sure I was not confusing it with CPR, but I guess in comment:3 I was thinking about let-up vs. let-down, and that some examples would look better if the analysis would work the other way. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 4 19:29:12 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 04 Jul 2016 19:29:12 -0000 Subject: [GHC] #10352: Properly link Haskell shared libs on ELF systems In-Reply-To: <045.f54c0b53e462b1ea305eb5f3c38d7688@haskell.org> References: <045.f54c0b53e462b1ea305eb5f3c38d7688@haskell.org> Message-ID: <060.46830fcbffe63faf1d6bb70540e1cba7@haskell.org> #10352: Properly link Haskell shared libs on ELF systems -------------------------------------+------------------------------------- Reporter: duncan | Owner: Type: task | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.11 (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: | -------------------------------------+------------------------------------- Changes (by Phyx-): * os: Linux => Unknown/Multiple Comment: I think this would work for Windows as well and would solve some issues with Dynamic linking there. For this to work on Windows we need a few things: name all the rts variants the same. e.g. `ghc-rts.dll` but place them in different folders: {{{ rts \ normal \ ghc-rts.dll \ threaded \ ghc-rts.dll \ profiled \ ghc-rts.dll }}} etc. We can then delay load the rts library. All the RTS versions should have the same ABI so that shouldn't be an issue. During compilation of a `.exe` we can then set the search path using `AddDllDirectory` to allow the loader to pick the correct `RTS` variants for the `.exe` and all the DLLs since they are all in the same process space as the `exe` and so will inherit the search path. For dynamic libraries we can override the `hs_init` function and do the same. I think we can use ld's `--wrap symbol` for this so existing code don't need any changing: http://ftp.gnu.org/pub/old-gnu/Manuals/ld-2.9.1/html_node/ld_3.html So I will re-classify this as being multiple platforms. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 4 19:57:52 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 04 Jul 2016 19:57:52 -0000 Subject: [GHC] #5987: Too many symbols in ghc package DLL In-Reply-To: <044.2d87ca11391c23e0fa5f3c5418ae791f@haskell.org> References: <044.2d87ca11391c23e0fa5f3c5418ae791f@haskell.org> Message-ID: <059.efc10a4a46b2488775fe2a2f9ff4abff@haskell.org> #5987: Too many symbols in ghc package DLL ---------------------------------+---------------------------------------- Reporter: igloo | Owner: Phyx- Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.5 Resolution: | Keywords: Operating System: Windows | Architecture: Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: 10352 | Blocking: 5355 Related Tickets: | Differential Rev(s): Wiki Page: | ---------------------------------+---------------------------------------- Changes (by Phyx-): * blockedby: => 10352 Comment: Quick update, dynamic linking now works again: {{{ $ ghc-stage2 -fforce-recomp test.hs -dynamic && ./test [1 of 1] Compiling Main ( test.hs, test.o ) Linking test.exe ... Hello World }}} And loader logs: {{{ Process Started: 0000000000400000 E:\temp\dynamic\test.exe ... DLL Loaded: 0000000070D00000 R:\GHC\libHSghc- prim-0.5.0.0-ghc8.1.20160628.dll DLL Loaded: 0000000067240000 R:\GHC\libHSrts-ghc8.1.20160628.dll ... DLL Loaded: 0000000069F80000 R:\GHC\libHSbase-4.9.0.0-ghc8.1.20160628.dll ... DLL Loaded: 000000006B740000 R:\GHC\libffi-6.dll ... DLL Loaded: 0000000069780000 R:\GHC\libHSinteger- gmp-1.0.0.1-ghc8.1.20160628.dll }}} Approach is written https://ghc.haskell.org/trac/ghc/wiki/WindowsDynamicLinking here and I'll keep updating it as I go. Code is not done but changes can be seen https://github.com/Mistuke/ghc/pull/5 on my Github. The major limitation in this version is that only the normal `rts` can be used. Due to the fact that we can't link with unknown symbols on Windows in the final link. After talking to `rwbarton` I believe this can be solved by a Windows version of #10352 and so temporarily stopping work on this so I can take a look at #10352 instead. Remaining: - Figure out the `ASSERT` failures in `compiler/stgSyn/CoreToStg.hs` - Fix dist building to include split dlls if split occurs - Implement mechanism to select right `rts` version. - Clean up code For reference, the sizes of the produced `dlls` are now also a tad smaller {{{ 695960 /r/GHC/libHSarray-0.5.1.1-ghc8.1.20160628.dll 11997540 /r/GHC/libHSbase-4.9.0.0-ghc8.1.20160628.dll 770941 /r/GHC/libHSbinary-0.8.3.0-ghc8.1.20160628.dll 1222357 /r/GHC/libHSbytestring-0.10.8.1-ghc8.1.20160628.dll 17275289 /r/GHC/libHSCabal-1.25.0.0-ghc8.1.20160628.dll 2327994 /r/GHC/libHScontainers-0.5.7.1-ghc8.1.20160628.dll 183756 /r/GHC/libHSdeepseq-1.4.2.0-ghc8.1.20160628.dll 386058 /r/GHC/libHSdirectory-1.2.6.2-ghc8.1.20160628.dll 224319 /r/GHC/libHSfilepath-1.4.1.0-ghc8.1.20160628.dll 47179898 /r/GHC/libHSghc-8.1-ghc8.1.20160628.dll 583840 /r/GHC/libHSghc-boot-8.1-ghc8.1.20160628.dll 476365 /r/GHC/libHSghc-boot-th-8.1-ghc8.1.20160628.dll 2004675 /r/GHC/libHSghci-8.1-ghc8.1.20160628.dll 3144663 /r/GHC/libHSghc-prim-0.5.0.0-ghc8.1.20160628.dll 1721465 /r/GHC/libHShaskeline-0.7.2.3-ghc8.1.20160628.dll 894721 /r/GHC/libHShoopl-3.10.2.1-ghc8.1.20160628.dll 318805 /r/GHC/libHShpc-0.6.0.3-ghc8.1.20160628.dll 761724 /r/GHC/libHSinteger-gmp-1.0.0.1-ghc8.1.20160628.dll 668894 /r/GHC/libHSpretty-1.1.3.3-ghc8.1.20160628.dll 264811 /r/GHC/libHSprocess-1.4.2.0-ghc8.1.20160628.dll 1680082 /r/GHC/libHSrts_debug-ghc8.1.20160628.dll 2182245 /r/GHC/libHSrts_l-ghc8.1.20160628.dll 1796551 /r/GHC/libHSrts_thr_debug-ghc8.1.20160628.dll 2466036 /r/GHC/libHSrts_thr_l-ghc8.1.20160628.dll 2206968 /r/GHC/libHSrts_thr-ghc8.1.20160628.dll 1949321 /r/GHC/libHSrts-ghc8.1.20160628.dll 4638331 /r/GHC/libHStemplate-haskell-2.11.0.0-ghc8.1.20160628.dll 1448186 /r/GHC/libHStime-1.6.0.1-ghc8.1.20160628.dll 1494791 /r/GHC/libHStransformers-0.5.2.0-ghc8.1.20160628.dll 2644212 /r/GHC/libHSWin32-2.3.1.1-ghc8.1.20160628.dll }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 4 21:31:24 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 04 Jul 2016 21:31:24 -0000 Subject: [GHC] #12354: Word foldl' isn't optimized as well as Int foldl' In-Reply-To: <045.bac6bcbeca1cabd22823ab5f537d5cc8@haskell.org> References: <045.bac6bcbeca1cabd22823ab5f537d5cc8@haskell.org> Message-ID: <060.878d70f21223e570e5132b7b03e64ab4@haskell.org> #12354: Word foldl' isn't optimized as well as Int foldl' -------------------------------------+------------------------------------- Reporter: kjslag | Owner: Type: bug | Status: patch Priority: normal | Milestone: Component: Compiler | Version: 8.0.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): Phab:D2376 Wiki Page: | -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"0bd7c4b4240a27d4e26290741394b31b48db7671/ghc" 0bd7c4b/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="0bd7c4b4240a27d4e26290741394b31b48db7671" Enum: Ensure that operations on Word fuse Test Plan: Validate, verify fusion Reviewers: austin, hvr Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2376 GHC Trac Issues: #12354 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 4 21:31:24 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 04 Jul 2016 21:31:24 -0000 Subject: [GHC] #12165: Multiple pattern type signatures accepted In-Reply-To: <047.0e810b3c040e7f9c575b82495a00aef7@haskell.org> References: <047.0e810b3c040e7f9c575b82495a00aef7@haskell.org> Message-ID: <062.4a294d6dedc6f13d696ca9c71af3125c@haskell.org> #12165: Multiple pattern type signatures accepted -------------------------------------+------------------------------------- Reporter: goldfire | Owner: seraphime Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: | PatternSynonyms, newcomer Operating System: Unknown/Multiple | Architecture: Type of failure: GHC accepts | Unknown/Multiple invalid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2361 Wiki Page: | -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"2a3af15270d1c04745b1c42e61bf4d5f6dbc8ad5/ghc" 2a3af152/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="2a3af15270d1c04745b1c42e61bf4d5f6dbc8ad5" Treat duplicate pattern synonym signatures as an error Fixes issue T12165 by banning duplicate pattern synonyms signatures. This seems to me the best solution because: 1) it is coherent with the way we treat other duplicate signatures 2) the typechecker currently doesn't try to apply a second signature to a pattern to see if it matches, probably because it assumes there is no more than one signature per object. Test Plan: ./validate Reviewers: goldfire, austin, mpickering, bgamari Reviewed By: mpickering, bgamari Subscribers: mpickering, thomie Differential Revision: https://phabricator.haskell.org/D2361 GHC Trac Issues: #12165 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 4 21:31:24 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 04 Jul 2016 21:31:24 -0000 Subject: [GHC] #12355: Invalid assembly in foreign prim In-Reply-To: <043.e628067e14a84102326ba14e6b406a11@haskell.org> References: <043.e628067e14a84102326ba14e6b406a11@haskell.org> Message-ID: <058.3c780a6863f29960ae8c2b9e6a3da567@haskell.org> #12355: Invalid assembly in foreign prim -------------------------------------+------------------------------------- Reporter: osa1 | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | 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 Ben Gamari ): In [changeset:"afec447cde1f97438bbc5bf7a31000e948c721eb/ghc" afec447/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="afec447cde1f97438bbc5bf7a31000e948c721eb" testsuite: Add testcase for #12355 Test Plan: Validate Reviewers: austin, osa1 Reviewed By: osa1 Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2377 GHC Trac Issues: #12355 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 4 21:32:48 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 04 Jul 2016 21:32:48 -0000 Subject: [GHC] #12354: Word foldl' isn't optimized as well as Int foldl' In-Reply-To: <045.bac6bcbeca1cabd22823ab5f537d5cc8@haskell.org> References: <045.bac6bcbeca1cabd22823ab5f537d5cc8@haskell.org> Message-ID: <060.2782d3dd19a9512154e36bdae378f3d4@haskell.org> #12354: Word foldl' isn't optimized as well as Int foldl' -------------------------------------+------------------------------------- Reporter: kjslag | Owner: Type: bug | Status: patch Priority: normal | Milestone: Component: Compiler | Version: 8.0.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): Phab:D2376 Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): Merged to `master`. Seems like this would be an easy thing to merge for 8.0.2. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 4 21:33:03 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 04 Jul 2016 21:33:03 -0000 Subject: [GHC] #12354: Word foldl' isn't optimized as well as Int foldl' In-Reply-To: <045.bac6bcbeca1cabd22823ab5f537d5cc8@haskell.org> References: <045.bac6bcbeca1cabd22823ab5f537d5cc8@haskell.org> Message-ID: <060.b609916a53aecbc7726a7761e48ec9de@haskell.org> #12354: Word foldl' isn't optimized as well as Int foldl' -------------------------------------+------------------------------------- Reporter: kjslag | Owner: Type: bug | Status: merge Priority: normal | Milestone: 8.0.2 Component: Compiler | Version: 8.0.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): Phab:D2376 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: patch => merge * milestone: => 8.0.2 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 4 21:37:35 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 04 Jul 2016 21:37:35 -0000 Subject: [GHC] #12165: Multiple pattern type signatures accepted In-Reply-To: <047.0e810b3c040e7f9c575b82495a00aef7@haskell.org> References: <047.0e810b3c040e7f9c575b82495a00aef7@haskell.org> Message-ID: <062.5f7a993a0155427a0ed0493ef3b6b7d7@haskell.org> #12165: Multiple pattern type signatures accepted -------------------------------------+------------------------------------- Reporter: goldfire | Owner: seraphime Type: bug | Status: merge Priority: normal | Milestone: 8.0.2 Component: Compiler | Version: 8.0.1 Resolution: | Keywords: | PatternSynonyms, newcomer Operating System: Unknown/Multiple | Architecture: Type of failure: GHC accepts | Unknown/Multiple invalid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2361 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => merge * milestone: => 8.0.2 Comment: Merged. Perhaps it would be worth trying to merge this to 8.0.2. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 4 21:47:42 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 04 Jul 2016 21:47:42 -0000 Subject: [GHC] #12357: Increasing maximum constraint tuple size significantly blows up compiler allocations In-Reply-To: <046.dd0f12e974ac3c5c9febd70397bf4138@haskell.org> References: <046.dd0f12e974ac3c5c9febd70397bf4138@haskell.org> Message-ID: <061.70f9409df235f27d86578ba070e47a4e@haskell.org> #12357: Increasing maximum constraint tuple size significantly blows up compiler allocations -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.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): Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): Here are the same results from comment:5 but shown in terms of absolute change. All allocations given in these tables are in bytes. ||= Change =||= alloc A =||= alloc B =||= name =|| || +7420720.0 || 4477200 || 11897920 || $wa5 (ghc-7.11.20150614:Encoding) || || +1869440.0 || 10348960 || 12218400 || $cgetUnique (ghc-7.11.20150614:Unique) || || +1538976.0 || 499856 || 2038832 || $wa3 (ghc-7.11.20150614:Encoding.) || || +998016.0 || 6526672 || 7524688 || (ghc-7.11.20150614:FastTypes.iBox) || || +810336.0 || 4372400 || 5182736 || (ghc-7.11.20150614:FastString.uniqueOfFS) || || +746304.0 || 3274992 || 4021296 || $ccompare1 (ghc-7.11.20150614:Module) || || +458528.0 || 5368328 || 5826856 || a11 (ghc-7.11.20150614:IOEnv) || || +375360.0 || 2830992 || 3206352 || $ccompare (ghc-7.11.20150614:Module) || || +277104.0 || 1640736 || 1917840 || (ghc-7.11.20150614:Unique.mkUnique) || || +276184.0 || 22040 || 298224 || (ghc-7.11.20150614:OccName.mkSuperDictSelOcc) || || +255936.0 || 320 || 256256 || sat_sjxb (ghc-7.11.20150614:TcRnMonad) || || +244352.0 || 58488 || 302840 || ds1 (ghc-7.11.20150614:LoadIface) || || +218960.0 || 905968 || 1124928 || (ghc-7.11.20150614:TysWiredIn.isBuiltInOcc_maybe) || || +172040.0 || 337216 || 509256 || (ghc-7.11.20150614:IfaceEnv.lookupOrig) || || +156400.0 || 672640 || 829040 || sat_s29U (ghc-7.11.20150614:UniqSupply) || || +152720.0 || 350440 || 503160 || (ghc-7.11.20150614:FastString.unpackFS) || || +146832.0 || 2029744 || 2176576 || (ghc-7.11.20150614:Binary.getByte1) || || +145360.0 || 1439680 || 1585040 || $wa1 (ghc-7.11.20150614:BinIface.) || || +142232.0 || 605144 || 747376 || $wa (ghc-7.11.20150614:FastString.) || || +137448.0 || 302448 || 439896 || (ghc-7.11.20150614:UniqSupply.takeUniqFromSupply) || || +131928.0 || 259992 || 391920 || $wa86 (ghc-7.11.20150614:Binary) || || +125120.0 || 1819648 || 1944768 || (ghc-7.11.20150614:UniqFM.lookupUFM) || || +125120.0 || 640832 || 765952 || a17 (ghc-7.11.20150614:UniqFM) || || +112056.0 || 765296 || 877352 || a10 (ghc-7.11.20150614:IOEnv) || || +109480.0 || 245336 || 354816 || (ghc-7.11.20150614:Name.mkExternalName) || || +106904.0 || 224336 || 331240 || (ghc-7.11.20150614:IfaceEnv.extendNameCache) || || +89424.0 || 318552 || 407976 || (ghc-7.11.20150614:Unique.mkVarOccUnique) || || +87952.0 || 1069664 || 1157616 || $wa3 (ghc-7.11.20150614:Binary.) || || +78200.0 || 283320 || 361520 || (ghc-7.11.20150614:FastString.mkFastStringByteString3) || || +74520.0 || 2068360 || 2142880 || $cget5 (ghc-7.11.20150614:IfaceType) || || +72680.0 || 1294840 || 1367520 || $cget4 (ghc-7.11.20150614:IfaceType) || || +72680.0 || 748080 || 820760 || $cget2 (ghc-7.11.20150614:IfaceType) || || +72680.0 || 787960 || 860640 || $cget1 (ghc-7.11.20150614:IfaceType) || || +63296.0 || 827536 || 890832 || (ghc-7.11.20150614:Unique.mkUniqueGrimily) || || +62560.0 || 269056 || 331616 || sat_s29W (ghc-7.11.20150614:UniqSupply) || || +62560.0 || 269056 || 331616 || sat_s29V (ghc-7.11.20150614:UniqSupply) || || +61088.0 || 143104 || 204192 || $wa2 (ghc-7.11.20150614:Encoding.) || || +49128.0 || 352488 || 401616 || (ghc-7.11.20150614:Name.nameUnique) || -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 4 22:21:02 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 04 Jul 2016 22:21:02 -0000 Subject: [GHC] #12240: Common Sense for Type Classes In-Reply-To: <050.3dcf7ad3ce6a480cdc5fe8435e755275@haskell.org> References: <050.3dcf7ad3ce6a480cdc5fe8435e755275@haskell.org> Message-ID: <065.53300fcd07d95f6608b7a5eda1735874@haskell.org> #12240: Common Sense for Type Classes -------------------------------------+------------------------------------- Reporter: Mathnerd314 | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 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 Mathnerd314): > This is only "common sense" if you discard the open world assumption I have not seen hide nor hair of this fabled "open world assumption", except a small section in Real World Haskell: > We can add new instances anywhere; they are not confined to the module where we define a typeclass. This feature of the typeclass system is referred to as its open world assumption. This refers to the ''declaration'' of instances, not instance resolution. If the proposal was to remove orphan instances, I would see the merit of bringing this up, but it does not seem relevant here. > (or accept incoherence), Consider this: {{{#!hs -- in A.hs class A a where f :: a -> Int -- in B.hs instance A Int where f _ = 1 foo = f (0 :: Int) -- in C.hs instance A Int where f _ = 2 bar = f (0 :: Int) -- in Main.hs main = print (foo,bar) -- (1,2) }}} It is a blatant violation of the Haskell Report ("A type may not be declared as an instance of a particular class more than once in the program."), yet it compiles in GHC with no extensions. Meanwhile, all I want to do is relax instantiation from "a single instance matches and no other instance unifies" to "a single instance unifies and no other instance unifies". This is only interesting in limited situations, such as the example in comment:4, and leaves all Haskell 98 instances unchanged. I do not see how it adds any incoherence, because in both rules only a single instance is allowed. > I don't claim to have any say in whether an implementation will or will not be accepted, but bear in mind that new features have an ongoing cost, even if guarded by language flags. Feel free to work on it if you like, but seeking wider input first might be a good idea to avoid working on something that is ultimately not merged. I have posted on Reddit, IRC, and this bugtracker; what's left besides Phabricator? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 5 01:24:27 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 05 Jul 2016 01:24:27 -0000 Subject: [GHC] #12357: Increasing maximum constraint tuple size significantly blows up compiler allocations In-Reply-To: <046.dd0f12e974ac3c5c9febd70397bf4138@haskell.org> References: <046.dd0f12e974ac3c5c9febd70397bf4138@haskell.org> Message-ID: <061.bba1f3d59537fcd9c809f71349e8308f@haskell.org> #12357: Increasing maximum constraint tuple size significantly blows up compiler allocations -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.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): Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): It looks like much of the trouble is that we are unpacking `OccNames` in `isBuiltInOcc_maybe`, which gets called in `LoadIface.loadDecl` by `IfaceEnv.lookupOrig`. This results in a great deal of allocations by `utf8DecodeString`, which eagerly decodes the entire string buffer into a `[Char]`. This eager behavior seems a bit silly. Unfortunately, I made a few quick attempts at making this decoding lazy but sadly it typically hurt allocations more than it helped due to thunk allocations It also seems a bit silly that we inspect the name itself to determine whether it is built-in. Afterall, there is a finite universe of built-in `OccName`s and we already know the `FastString` hash of the `OccName` we are testing, so it seems like this really should just be a `UniqFM` lookup. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 5 04:37:57 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 05 Jul 2016 04:37:57 -0000 Subject: [GHC] #11350: Allow visible type application in patterns In-Reply-To: <051.b16517d65bfaaca2db1f23781a666611@haskell.org> References: <051.b16517d65bfaaca2db1f23781a666611@haskell.org> Message-ID: <066.002829851286106169658e23c76240fb@haskell.org> #11350: Allow visible type application in patterns -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.1 Resolution: | Keywords: | TypeApplications 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 Iceland_jack): Notes, similar to [https://hackage.haskell.org/package/base-4.9.0.0/docs /GHC-OverloadedLabels.html GHC.OverloadedLabels.IsLabel]: {{{#!hs class IsLeibel (str::Symbol) a where fromLeibel :: a }}} would the following work {{{#!hs instance forall x r a. HasField x r a => IsLeibel x (r -> a) where fromLeibel :: r -> a fromLeibel @x = getField @x }}} Does `fromLeibel @x` bring `x` into scope, shadowing `instance forall x r a.`? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 5 08:21:50 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 05 Jul 2016 08:21:50 -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.fbd8d29578d0890edc2db25278cbf4b6@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 akio): Replying to [comment:23 rwbarton]: > I don't think parsing `f a b {-# SCC #-} d e` as `f a b ({-# SCC #-} d e)` is even an option, really, since these pragmas must be ignorable by compilers that don't understand them. Agreed. > Also, I think/hope this proposal does not change the parsing of any program that currently parses, right? I believe this is the case, although I don't have a proof. My rough argument is: 1. This extension doesn't introduce any new conflict in the parser (shift/reduce or reduce/reduce) 2. By chasing the new grammar you can see that `do`, lambda, etc. continue to parse as a `lexp`. So if there is any change in the parsing of any currently-valid program, then it must be a result of somehow triggering an existing ambiguity in the grammar, but this seems unlikely. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 5 08:24:51 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 05 Jul 2016 08:24:51 -0000 Subject: [GHC] #12357: Increasing maximum constraint tuple size significantly blows up compiler allocations In-Reply-To: <046.dd0f12e974ac3c5c9febd70397bf4138@haskell.org> References: <046.dd0f12e974ac3c5c9febd70397bf4138@haskell.org> Message-ID: <061.c4eaa8d2046775df5c7012aaa4ea671c@haskell.org> #12357: Increasing maximum constraint tuple size significantly blows up compiler allocations -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.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): Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): I've put up a few attempts at reducing some of the costs associated with `FastString` operations and in particular `isBuiltInOcc_maybe`. The most promising so far is Phab:D2385, which reworks `isBuiltInOcc` to avoid unpacking the name being checked. It does this by moving the implementation away from `String` pattern matching and towards a `FastString` lookup in a `UniqFM`. Initial indications suggest this reduces allocations by around 5% when compiling `nofib/real/fulsom/Shape.hs`. Another thing I noticed while tracking this down is the behavior of `concatFS`, which unpacks the the `FastString`s being concatenated and then builds a new `FastString` from the resulting list. It seems like there might be slightly better constant factors to be had by simply concatenating the `ByteString`s themselves. I have tried reworking this in Phab:D2384, although I don't yet have solid numbers characterizing its effect. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 5 08:37:40 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 05 Jul 2016 08:37:40 -0000 Subject: [GHC] #12364: Demand analysis for sum types In-Reply-To: <046.d2210fe5d78e7148b495c8c2b1cf9322@haskell.org> References: <046.d2210fe5d78e7148b495c8c2b1cf9322@haskell.org> Message-ID: <061.3c94dad713dba60d6b98f70ba38549c5@haskell.org> #12364: Demand analysis for sum types -------------------------------------+------------------------------------- Reporter: nomeata | Owner: Type: task | 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 nomeata): osa1 mentioned that they actually have a working implementation of this in https://github.com/osa1/ghc/blob/rebase-second- try/compiler/basicTypes/Demand.hs#L188, so I’ll stop working on my copy. My code is still in wip/T12364, but probably not much use. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 5 08:46:11 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 05 Jul 2016 08:46:11 -0000 Subject: [GHC] #12364: Demand analysis for sum types In-Reply-To: <046.d2210fe5d78e7148b495c8c2b1cf9322@haskell.org> References: <046.d2210fe5d78e7148b495c8c2b1cf9322@haskell.org> Message-ID: <061.7304482b29cee8892c1f3df069b382e8@haskell.org> #12364: Demand analysis for sum types -------------------------------------+------------------------------------- Reporter: nomeata | Owner: Type: task | 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 osa1): Yes, we implemented it with @jmct and it worked fine in our tests. Only problem is: We don't have a recursive type check, so for lists etc. it takes really long time (because it iterates 20 times as that's the hard- coded hard-limit for demand analysis iterations, specified in DmdAnal.hs). We also implemented CPR if you need that... -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 5 08:48:19 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 05 Jul 2016 08:48:19 -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.de1f0eb5d8d689edac058e16d00105b1@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 akio): Replying to [comment:24 Iceland_jack]: > **Edit**: Will it let you write Yes, your examples should be fine, and my preliminary implementation successfully parses them. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 5 08:49:17 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 05 Jul 2016 08:49:17 -0000 Subject: [GHC] #12364: Demand analysis for sum types In-Reply-To: <046.d2210fe5d78e7148b495c8c2b1cf9322@haskell.org> References: <046.d2210fe5d78e7148b495c8c2b1cf9322@haskell.org> Message-ID: <061.863efe8745e1295f29335fa063e9ba1d@haskell.org> #12364: Demand analysis for sum types -------------------------------------+------------------------------------- Reporter: nomeata | Owner: Type: task | 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 osa1): Our branch is big because we do worker/wrapper for sums, CPR, unpacking sum fields in DataCons etc. If you only need demand analysis I suggest just copying Demand.hs and DmdAnal.hs. You may then need to fix worker/wrapper pass so that it won't crash when it sees a sum demand or cpr etc. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 5 09:00:06 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 05 Jul 2016 09:00:06 -0000 Subject: [GHC] #12357: Increasing maximum constraint tuple size significantly blows up compiler allocations In-Reply-To: <046.dd0f12e974ac3c5c9febd70397bf4138@haskell.org> References: <046.dd0f12e974ac3c5c9febd70397bf4138@haskell.org> Message-ID: <061.99eeb38ada38e4174193470dc9c572a3@haskell.org> #12357: Increasing maximum constraint tuple size significantly blows up compiler allocations -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.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): Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): The `UniqFM` approach appears to reduce allocations on `Shape` from 130 MByte to 112 MByte. Sadly this is still a fair bit above the allocations before the constraint tuple change, which was around 95 MByte. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 5 09:31:47 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 05 Jul 2016 09:31:47 -0000 Subject: [GHC] #12357: Increasing maximum constraint tuple size significantly blows up compiler allocations In-Reply-To: <046.dd0f12e974ac3c5c9febd70397bf4138@haskell.org> References: <046.dd0f12e974ac3c5c9febd70397bf4138@haskell.org> Message-ID: <061.07c221b98d788b1fe7a2d38d8b88031b@haskell.org> #12357: Increasing maximum constraint tuple size significantly blows up compiler allocations -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.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): Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): It appears that much of the remaining difference is due to the construction of the superclass selector `OccName`s, which looks like this, {{{#!hs mkSuperDictSelOcc :: Int -- ^ Index of superclass, e.g. 3 -> OccName -- ^ Class, e.g. @Ord@ -> OccName -- ^ Derived 'Occname', e.g. @$p3Ord@ mkSuperDictSelOcc index cls_tc_occ = mk_deriv varName "$p" (show index ++ occNameString cls_tc_occ) }}} This is rather inefficient as we first decode the class's `OccName`, then reencode it. After fixing `concatFS` with Phab:D2384 and redefining this helper as {{{#!hs mkSuperDictSelOcc index cls_tc_occ = mkOccNameFS varName $ concatFS [fsLit "$p", fsLit $ show index, occNameFS cls_tc_occ] }}} I find that allocations return to 96MBytes, which is very close to the allocations prior to the superclass constraint patch. I suspect that this rework should be performed to all of the helpers in `OccName`. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 5 09:53:25 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 05 Jul 2016 09:53:25 -0000 Subject: [GHC] #12357: Increasing maximum constraint tuple size significantly blows up compiler allocations In-Reply-To: <046.dd0f12e974ac3c5c9febd70397bf4138@haskell.org> References: <046.dd0f12e974ac3c5c9febd70397bf4138@haskell.org> Message-ID: <061.b551d38175128a393ac2e40d2493caed@haskell.org> #12357: Increasing maximum constraint tuple size significantly blows up compiler allocations -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.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): Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): Another related efficiency issue can be found in `isDerivedOccName`, which decodes the entire `OccName` just to check the first two characters. One potential improvement here would be to use a bit in `OccName` (e.g. one of the many unused bits belonging to the `Namespace` field) to encode a "is derived" flag. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 5 11:37:24 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 05 Jul 2016 11:37:24 -0000 Subject: [GHC] #4012: Compilation results are not deterministic In-Reply-To: <043.9c3dc141e8901acb12e4d7c1e6038096@haskell.org> References: <043.9c3dc141e8901acb12e4d7c1e6038096@haskell.org> Message-ID: <058.ed131d33be1ac24f3a98db31e0cb1717@haskell.org> #4012: Compilation results are not deterministic -------------------------------------+------------------------------------- Reporter: kili | Owner: niteria Type: bug | Status: new Priority: high | Milestone: 8.2.1 Component: Compiler | Version: 6.12.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Other | Test Case: Blocked By: 11362 | Blocking: 12262 Related Tickets: #10424 | Differential Rev(s): Phab:D910, | Phab:D1073, Phab:D1133, Phab:D1192, | Phab:D1268, Phab:D1360, Phab:D1373, Wiki Page: | Phab:D1396, Phab:D1457, Phab:D1468, DeterministicBuilds | Phab:D1487, Phab:D1504, Phab:D1508 -------------------------------------+------------------------------------- Comment (by Bartosz Nitka ): In [changeset:"e10497b9a3622265b88caa60590ed620ff3d33e2/ghc" e10497b/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="e10497b9a3622265b88caa60590ed620ff3d33e2" Kill some varEnvElts I was able to hide the nondeterminism in some specialized function, which I believe will be useful in other places. GHC Trac: #4012 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 5 11:54:07 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 05 Jul 2016 11:54:07 -0000 Subject: [GHC] #12357: Increasing maximum constraint tuple size significantly blows up compiler allocations In-Reply-To: <046.dd0f12e974ac3c5c9febd70397bf4138@haskell.org> References: <046.dd0f12e974ac3c5c9febd70397bf4138@haskell.org> Message-ID: <061.60c89f9702b9ca52fea47f669d5bdf52@haskell.org> #12357: Increasing maximum constraint tuple size significantly blows up compiler allocations -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.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): Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): Replying to [comment:13 bgamari]: > Another related efficiency issue can be found in `isDerivedOccName` ... While this is technically true, `isDerivedOccName` is only used in a few non-essential places so it is likely fine that it isn't terribly efficient. It's likely not worth adding a flag as proposed. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 5 12:50:47 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 05 Jul 2016 12:50:47 -0000 Subject: [GHC] #12151: GHC 8 allows ambiguous type without AllowAmbiguousTypes In-Reply-To: <045.025d1a9dae2fe540211f842ca4b9eb91@haskell.org> References: <045.025d1a9dae2fe540211f842ca4b9eb91@haskell.org> Message-ID: <060.91c047d2fcb80573203df5e221c8476b@haskell.org> #12151: GHC 8 allows ambiguous type without AllowAmbiguousTypes -------------------------------------+------------------------------------- Reporter: thomie | Owner: 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: Incorrect | Unknown/Multiple warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: #7437 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Simon Peyton Jones ): In [changeset:"85aa6ef09346e841abf4e089b24c7f783286cd74/ghc" 85aa6ef0/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="85aa6ef09346e841abf4e089b24c7f783286cd74" Check generic-default method for ambiguity Fixes Trac #7497 and #12151. In some earlier upheaval I introduced a bug in the ambiguity check for genreric-default method. This patch fixes it. But in fixing it I realised that the sourc-location of any such error message was bogus, so I fixed that too, which involved a slightly wider change; see the comments with TcMethInfo. }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 5 12:50:47 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 05 Jul 2016 12:50:47 -0000 Subject: [GHC] #7497: qsem001 and qsemn001 fail in HEAD In-Reply-To: <044.c47a0fecf45da0cc7278c09c93ba81dc@haskell.org> References: <044.c47a0fecf45da0cc7278c09c93ba81dc@haskell.org> Message-ID: <059.f0e84b7db48c8bb7c32db1c03780f411@haskell.org> #7497: qsem001 and qsemn001 fail in HEAD -------------------------------------+--------------------------------- Reporter: igloo | Owner: simonmar Type: bug | Status: closed Priority: normal | Milestone: Component: Test Suite | Version: 7.7 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | -------------------------------------+--------------------------------- Comment (by Simon Peyton Jones ): In [changeset:"85aa6ef09346e841abf4e089b24c7f783286cd74/ghc" 85aa6ef0/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="85aa6ef09346e841abf4e089b24c7f783286cd74" Check generic-default method for ambiguity Fixes Trac #7497 and #12151. In some earlier upheaval I introduced a bug in the ambiguity check for genreric-default method. This patch fixes it. But in fixing it I realised that the sourc-location of any such error message was bogus, so I fixed that too, which involved a slightly wider change; see the comments with TcMethInfo. }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 5 12:53:13 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 05 Jul 2016 12:53:13 -0000 Subject: [GHC] #7437: peculiar behaviour with default instances and type variables In-Reply-To: <042.0fb474a7e7daa2f1660f34dd883e2b94@haskell.org> References: <042.0fb474a7e7daa2f1660f34dd883e2b94@haskell.org> Message-ID: <057.8caa9cf9bf09656663a15ec2eec348b7@haskell.org> #7437: peculiar behaviour with default instances and type variables -------------------------------------+------------------------------------- Reporter: bos | Owner: simonpj Type: bug | Status: new Priority: normal | Milestone: Component: Test Suite | Version: 7.6.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC accepts | Unknown/Multiple invalid program | Test Case: Blocked By: | Blocking: Related Tickets: #12151 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): In [changeset:"85aa6ef09346e841abf4e089b24c7f783286cd74/ghc" 85aa6ef0/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="85aa6ef09346e841abf4e089b24c7f783286cd74" Check generic-default method for ambiguity Fixes Trac #7497 and #12151. In some earlier upheaval I introduced a bug in the ambiguity check for genreric-default method. This patch fixes it. But in fixing it I realised that the sourc-location of any such error message was bogus, so I fixed that too, which involved a slightly wider change; see the comments with TcMethInfo. }}} The commit message has a typo about the ticket. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 5 12:54:52 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 05 Jul 2016 12:54:52 -0000 Subject: [GHC] #7437: peculiar behaviour with default instances and type variables In-Reply-To: <042.0fb474a7e7daa2f1660f34dd883e2b94@haskell.org> References: <042.0fb474a7e7daa2f1660f34dd883e2b94@haskell.org> Message-ID: <057.ff82f9f70d4d2364a4f00c300a333ab4@haskell.org> #7437: peculiar behaviour with default instances and type variables -------------------------------------+------------------------------------- Reporter: bos | Owner: simonpj Type: bug | Status: closed Priority: normal | Milestone: Component: Test Suite | Version: 7.6.1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: GHC accepts | Test Case: invalid program | typecheck/should_fail/T7437 Blocked By: | Blocking: Related Tickets: #12151 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * testcase: => typecheck/should_fail/T7437 * status: new => closed * resolution: => fixed -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 5 12:55:44 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 05 Jul 2016 12:55:44 -0000 Subject: [GHC] #12151: GHC 8 allows ambiguous type without AllowAmbiguousTypes In-Reply-To: <045.025d1a9dae2fe540211f842ca4b9eb91@haskell.org> References: <045.025d1a9dae2fe540211f842ca4b9eb91@haskell.org> Message-ID: <060.15b99892d78252bbd870ff9deea6b997@haskell.org> #12151: GHC 8 allows ambiguous type without AllowAmbiguousTypes -------------------------------------+------------------------------------- Reporter: thomie | Owner: Type: bug | Status: merge Priority: normal | Milestone: 8.0.2 Component: Compiler (Type | Version: 8.0.1 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Incorrect | Test Case: warning at compile-time | typecheck/should_fail/T12151 Blocked By: | Blocking: Related Tickets: #7437 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * testcase: => typecheck/should_fail/T12151 * status: new => merge * milestone: => 8.0.2 Comment: Could merge, but only if it goes easily -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 5 13:46:26 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 05 Jul 2016 13:46:26 -0000 Subject: [GHC] #12133: ConstraintKinds inference failure (regression from 7.10) In-Reply-To: <047.c733b50527f5eb857c28d94b329c6c5a@haskell.org> References: <047.c733b50527f5eb857c28d94b329c6c5a@haskell.org> Message-ID: <062.1033437f51e7685a367f878c7abde220@haskell.org> #12133: ConstraintKinds inference failure (regression from 7.10) ---------------------------------+---------------------------------------- Reporter: goldfire | Owner: Type: bug | Status: new Priority: normal | Milestone: 8.0.2 Component: Compiler | Version: 8.0.1 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 simonpj): * milestone: => 8.0.2 Comment: I think this is another manifestation of some bugs in my implementation of recursive superclasses, which was in 8.0. Happily it works just fine in HEAD. The commit that that may have fixed it is (see #12175) {{{ commit ce97b7298d54bdfccd9dcf366a69c5617b4eb43f Author: Simon Peyton Jones Date: Wed Jun 22 14:17:58 2016 +0100 Expand given superclasses more eagerly }}} but I have not tested this. I'm not sure how vigorously we should try to get a fix into 8.0.2, but I'll milestone it as such. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 5 14:02:52 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 05 Jul 2016 14:02:52 -0000 Subject: [GHC] #12365: Update documentation for partial type signatures Message-ID: <047.cbfa181c69d689f1b05c74fd008c67ae@haskell.org> #12365: Update documentation for partial type signatures -------------------------------------+------------------------------------- Reporter: goldfire | Owner: 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: -------------------------------------+------------------------------------- In the [https://downloads.haskell.org/~ghc/master/users- guide/glasgow_exts.html#partial-type-signatures documentation] for partial type signatures, I found several bits that are out of date: - There are several sample error messages given. These have been substantively reworded ({{{Found hole `_` with type: ...}}} to {{{Found type wildcard `_` standing for ...}}}) where I find the new wording much clearer. - In the "Where can they occur?" section, there's no mention of `TypeApplications`, which is a new context where they can appear. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 5 14:23:34 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 05 Jul 2016 14:23:34 -0000 Subject: [GHC] #11385: Unify named wildcards in different type applications In-Reply-To: <051.0076b412916fb4cfc0823d8e3d44b32d@haskell.org> References: <051.0076b412916fb4cfc0823d8e3d44b32d@haskell.org> Message-ID: <066.609e5a7884891a76e37bf3817047199f@haskell.org> #11385: Unify named wildcards in different type applications -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.1 checker) | Keywords: Resolution: | NamedWildCards 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 goldfire): Just seeing this now (missed it the first time it went through my inbox). I'm uncertain about this one. The current behavior is in line with the documentation, in that both arguments to, e.g., `const` are ''different'' types. So I think it's behaving according to spec. Should the spec change? Perhaps. If I recall correctly, there was a long and tortuous debate about the scoping of named wildcards, with all sides having good arguments in their favor. The nice thing about the current rule is that it's exceedingly simple and easy to predict. With your proposed rule, then you could write `f @_a () @_a` and have the two `_a`s share a scope. So I think I've convinced myself to lean against this idea, but I'm open to argument. A better solution is to allow visible type ''abstraction'': {{{ asTypeOf = \ @a -> const @a @a }}} That way, you can say exactly what you mean. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 5 14:29:03 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 05 Jul 2016 14:29:03 -0000 Subject: [GHC] #4012: Compilation results are not deterministic In-Reply-To: <043.9c3dc141e8901acb12e4d7c1e6038096@haskell.org> References: <043.9c3dc141e8901acb12e4d7c1e6038096@haskell.org> Message-ID: <058.602f4d8bc3cae077455f66e8dbe8ae29@haskell.org> #4012: Compilation results are not deterministic -------------------------------------+------------------------------------- Reporter: kili | Owner: niteria Type: bug | Status: new Priority: high | Milestone: 8.2.1 Component: Compiler | Version: 6.12.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Other | Test Case: Blocked By: 11362 | Blocking: 12262 Related Tickets: #10424 | Differential Rev(s): Phab:D910, | Phab:D1073, Phab:D1133, Phab:D1192, | Phab:D1268, Phab:D1360, Phab:D1373, Wiki Page: | Phab:D1396, Phab:D1457, Phab:D1468, DeterministicBuilds | Phab:D1487, Phab:D1504, Phab:D1508 -------------------------------------+------------------------------------- Comment (by Bartosz Nitka ): In [changeset:"55e43a6f9ef64cf31faca350f8bf86f5f5acb36a/ghc" 55e43a6f/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="55e43a6f9ef64cf31faca350f8bf86f5f5acb36a" Use DVarEnv for vectInfoVar This makes sure that we don't introduce unnecessary nondeterminism from vectorization. Also updates dph submodule to reflect the change in types. GHC Trac: #4012 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 5 14:34:31 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 05 Jul 2016 14:34:31 -0000 Subject: [GHC] #12249: Template Haskell top level scoping error In-Reply-To: <046.2c212e8451a2f7a23ceaf92c7fd020ab@haskell.org> References: <046.2c212e8451a2f7a23ceaf92c7fd020ab@haskell.org> Message-ID: <061.13028b77a1d7f0cc6ba0aad96e6c4daa@haskell.org> #12249: Template Haskell top level scoping error -------------------------------------+------------------------------------- Reporter: simonpj | Owner: 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 goldfire): Your last comment suggests a way to think about all of this: Each ''declaration group'' (as defined in the [https://downloads.haskell.org/~ghc/latest/docs/html/users_guide/glasgow_exts.html #template-haskell manual]) is its own unnamed module that exports all of its symbols. That actually might not be a bad way of implementing it either. (And `newName` identifiers should never be exported, as per discussion in comment:13:ticket:10599, yet to be finished.) In any case, I still say you're building some sort of ad-hoc implicit module system. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 5 14:56:39 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 05 Jul 2016 14:56:39 -0000 Subject: [GHC] #12240: Common Sense for Type Classes In-Reply-To: <050.3dcf7ad3ce6a480cdc5fe8435e755275@haskell.org> References: <050.3dcf7ad3ce6a480cdc5fe8435e755275@haskell.org> Message-ID: <065.d24452c3b619e493af97e55a6a7e94b1@haskell.org> #12240: Common Sense for Type Classes -------------------------------------+------------------------------------- Reporter: Mathnerd314 | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 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): Two quite separate reactions to this: 1. You can already do what you want, if you rephrase your instance. From the initial post: {{{#!hs instance (a ~ Int, b ~ Char) => C a b where ... }}} will have the behavior you want. The idea is that you're creating a universal instance (i.e., one that matches any pair of types) but then GHC must solve `a ~ Int` and `b ~ Char`, which will unify your type variables. 2. As a "GHC Insider", I'm quite leery of blocking the door to "GHC Outsiders". See [https://www.reddit.com/r/haskell/comments/4isua9/ghc_development_outsidein/ this provocation] and [https://ghc.haskell.org/trac/ghc/blog/ContributingToGhc Simon's response]. I am in full agreement with Simon that we must do better here. However, adding a new feature to GHC is very, very expensive. Phabricator has well-written reasons why; see "Rejecting patches" on [https://secure.phabricator.com/book/phabcontrib/article/contributing_code/ this page]. (My reference to Phab here is technically unrelated to GHC's use of Phab. It's just that Phab is another open source project, and its articulation of barriers to entry is much more advanced than GHC's.) At the moment, the original poster has gotten other member of the community to say that they wouldn't actively block the implementation of your idea; I'm afraid this is hardly a ringing endorsement. You ask about another place to post. I see a bunch of proposals go through [https://mail.haskell.org/mailman/listinfo/haskell-cafe Haskell- cafe], where the level of discourse is quite high (as with all Haskell venues I've seen -- a wonderful aspect of our community!). But I don't want you to waste time posting in yet another place, because I tend to doubt that your patch will be accepted without the support of some more prominent, long-standing members of our community. A final point here is that the door from "GHC Outsider" to "GHC Insider" is surely open. The best way to nudge your way in, I think, is to find a feature request that is smallish and already has support. Implement that feature. You'll learn a whole lot about the compiler, and hopefully make a friend or two in the process. Repeat. After a few patches, you'll be well on your way to "GHC Insider". -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 5 14:58:50 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 05 Jul 2016 14:58:50 -0000 Subject: [GHC] #11350: Allow visible type application in patterns In-Reply-To: <051.b16517d65bfaaca2db1f23781a666611@haskell.org> References: <051.b16517d65bfaaca2db1f23781a666611@haskell.org> Message-ID: <066.8aaa8a557b18c2e95bc0b9d736dc3fe9@haskell.org> #11350: Allow visible type application in patterns -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.1 Resolution: | Keywords: | TypeApplications 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 goldfire): That's a great question. It would have to be addressed in the design. I lean toward "no", because this seems useless other than for renaming. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 5 14:59:09 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 05 Jul 2016 14:59:09 -0000 Subject: [GHC] #12363: Type application for infix In-Reply-To: <051.833fc99ca846ecc78974bf61eb05e05f@haskell.org> References: <051.833fc99ca846ecc78974bf61eb05e05f@haskell.org> Message-ID: <066.94c0ef75e61430a51aa158a04a29da03@haskell.org> #12363: Type application for infix -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: 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: | -------------------------------------+------------------------------------- Comment (by Iceland_jack): In my current code I need to give a type hint to an assignment {{{#!hs ptr := @elt value }}} Amazingly this can be emulated with some trickery {{{#!hs -- infixl 0 ◃, <|, ▹, |> -- (◃) = flip ($) -- (<|) = flip ($) -- (▹) = ($) -- (|>) = ($) ptr <|(:=) @elt|> value }}} but at that point this is clearer {{{#!hs assign @elt ptr value }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 5 15:03:22 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 05 Jul 2016 15:03:22 -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.1be369d598efa2484c77f8aee4e699e8@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 goldfire): Replying to [comment:22 simonpj]: > I'm one of those who thinks that the fact that `f R { x = e }` means `f (R { x = e })` is a mistake :-). > I agree with you here, but I think the proposal in this ticket is still sensible, given that the perhaps-unexpected parsing started with a keyword. In the record update case, the perhaps-unexpected parsing isn't known until the open-brace, even though your brain has to parse the preceding space differently. To me, that's the real problem with the parsing of record-update: it's not left-to-right. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 5 15:20:06 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 05 Jul 2016 15:20:06 -0000 Subject: [GHC] #12245: Deriving Data at higher kinds In-Reply-To: <046.fc248d7aec0de3523dca25d70e6f7b1d@haskell.org> References: <046.fc248d7aec0de3523dca25d70e6f7b1d@haskell.org> Message-ID: <061.b0612d564ddc96aaaac0547e016b3396@haskell.org> #12245: Deriving Data at higher kinds -------------------------------------+------------------------------------- Reporter: simonpj | Owner: simonpj 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:"895eefa8447a2886e77fdedcbca8047263c88db7/ghc" 895eefa8/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="895eefa8447a2886e77fdedcbca8047263c88db7" Make unique auxiliary function names in deriving In deriving for Data, we make some auxiliary functions, but they didn't always get distinct names (Trac #12245). This patch fixes it by using the same mechanism as for dictionary functions, namely chooseUniqueOccTc. Some assocated refactoring came along for the ride. }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 5 15:20:06 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 05 Jul 2016 15:20:06 -0000 Subject: [GHC] #12133: ConstraintKinds inference failure (regression from 7.10) In-Reply-To: <047.c733b50527f5eb857c28d94b329c6c5a@haskell.org> References: <047.c733b50527f5eb857c28d94b329c6c5a@haskell.org> Message-ID: <062.bff3d7dccd72ab90b87df86a6e1f345e@haskell.org> #12133: ConstraintKinds inference failure (regression from 7.10) ---------------------------------+---------------------------------------- Reporter: goldfire | Owner: Type: bug | Status: new Priority: normal | Milestone: 8.0.2 Component: Compiler | Version: 8.0.1 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: | ---------------------------------+---------------------------------------- Comment (by Simon Peyton Jones ): In [changeset:"6cedef01e00e95517a546a72592ba6ff07bac605/ghc" 6cedef01/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="6cedef01e00e95517a546a72592ba6ff07bac605" Test Trac #12133 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 5 15:20:30 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 05 Jul 2016 15:20:30 -0000 Subject: [GHC] #12133: ConstraintKinds inference failure (regression from 7.10) In-Reply-To: <047.c733b50527f5eb857c28d94b329c6c5a@haskell.org> References: <047.c733b50527f5eb857c28d94b329c6c5a@haskell.org> Message-ID: <062.08a98820dde26d52e02f35c189ec693e@haskell.org> #12133: ConstraintKinds inference failure (regression from 7.10) -------------------------------------+------------------------------------- Reporter: goldfire | Owner: Type: bug | Status: new Priority: normal | Milestone: 8.0.2 Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Linux | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | typecheck/should_compile/T12133 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * testcase: => typecheck/should_compile/T12133 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 5 15:21:57 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 05 Jul 2016 15:21:57 -0000 Subject: [GHC] #12245: Deriving Data at higher kinds In-Reply-To: <046.fc248d7aec0de3523dca25d70e6f7b1d@haskell.org> References: <046.fc248d7aec0de3523dca25d70e6f7b1d@haskell.org> Message-ID: <061.fcb363313a0c11b57dfc81ec5569aa22@haskell.org> #12245: Deriving Data at higher kinds -------------------------------------+------------------------------------- Reporter: simonpj | Owner: simonpj 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: | deriving/should_compile/T12245 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * status: new => closed * testcase: => deriving/should_compile/T12245 * resolution: => fixed Comment: The presenting bug is fixed. I agree that #2256 is a better solution, but it's much further off. Meanwhile I'll close this. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 5 16:28:40 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 05 Jul 2016 16:28:40 -0000 Subject: [GHC] #12238: Many tests fail when BuildFlavour == perf-llvm and DYNAMIC_GHC_PROGRAMS == NO In-Reply-To: <044.4fede5f9eea8d5fff3be85b1c00e138e@haskell.org> References: <044.4fede5f9eea8d5fff3be85b1c00e138e@haskell.org> Message-ID: <059.8c3465a9fff4c989a66514b5038002c2@haskell.org> #12238: Many tests fail when BuildFlavour == perf-llvm and DYNAMIC_GHC_PROGRAMS == NO -----------------------------------+-------------------------------------- Reporter: erikd | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.1 Resolution: | Keywords: Operating System: Linux | Architecture: x86_64 (amd64) Type of failure: Other | Test Case: Blocked By: | Blocking: Related Tickets: #12230, #12169 | Differential Rev(s): Wiki Page: | -----------------------------------+-------------------------------------- Changes (by thomie): * related: #12230 => #12230, #12169 @@ -1,1 +1,1 @@ - Ticket spawned from #12240. + Ticket spawned from #12230. New description: Ticket spawned from #12230. Some time just before commit a33b498d5f648a576dac6d219115866f05721196 about 40 tests started failing with `BuildFlavour` set to `perf-llvm`. @simonmar suggested also testing with `DYNAMIC_GHC_PROGRAMS` set to `NO` which results on over 700 of the tests failing. @simonmar suggests something is broken in the LLVM backend or in the linker. -- Comment: Maybe #12169 is related. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 5 16:40:03 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 05 Jul 2016 16:40:03 -0000 Subject: [GHC] #4012: Compilation results are not deterministic In-Reply-To: <043.9c3dc141e8901acb12e4d7c1e6038096@haskell.org> References: <043.9c3dc141e8901acb12e4d7c1e6038096@haskell.org> Message-ID: <058.f158ddfd30c745b5cf07b324e6abed78@haskell.org> #4012: Compilation results are not deterministic -------------------------------------+------------------------------------- Reporter: kili | Owner: niteria Type: bug | Status: new Priority: high | Milestone: 8.2.1 Component: Compiler | Version: 6.12.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Other | Test Case: Blocked By: 11362 | Blocking: 12262 Related Tickets: #10424 | Differential Rev(s): Phab:D910, | Phab:D1073, Phab:D1133, Phab:D1192, | Phab:D1268, Phab:D1360, Phab:D1373, Wiki Page: | Phab:D1396, Phab:D1457, Phab:D1468, DeterministicBuilds | Phab:D1487, Phab:D1504, Phab:D1508 -------------------------------------+------------------------------------- Comment (by Bartosz Nitka ): In [changeset:"27fc75b2fea014006964eafe53b3ae17e058d75b/ghc" 27fc75b2/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="27fc75b2fea014006964eafe53b3ae17e058d75b" Document codegen nondeterminism We don't care about bit-for-bit reproducibility, so I'm just documenting this as a possible source. GHC Trac: #4012 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 5 16:42:00 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 05 Jul 2016 16:42:00 -0000 Subject: [GHC] #4012: Compilation results are not deterministic In-Reply-To: <043.9c3dc141e8901acb12e4d7c1e6038096@haskell.org> References: <043.9c3dc141e8901acb12e4d7c1e6038096@haskell.org> Message-ID: <058.85b858976088347510f1f92234af5824@haskell.org> #4012: Compilation results are not deterministic -------------------------------------+------------------------------------- Reporter: kili | Owner: niteria Type: bug | Status: new Priority: high | Milestone: 8.2.1 Component: Compiler | Version: 6.12.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Other | Test Case: Blocked By: 11362 | Blocking: 12262 Related Tickets: #10424 | Differential Rev(s): Phab:D910, | Phab:D1073, Phab:D1133, Phab:D1192, | Phab:D1268, Phab:D1360, Phab:D1373, Wiki Page: | Phab:D1396, Phab:D1457, Phab:D1468, DeterministicBuilds | Phab:D1487, Phab:D1504, Phab:D1508 -------------------------------------+------------------------------------- Comment (by Bartosz Nitka ): In [changeset:"18b782e3209764c318da46b378b517749af14685/ghc" 18b782e3/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="18b782e3209764c318da46b378b517749af14685" Kill varEnvElts in zonkEnvIds This localizes the nondeterminism that varEnvElts could have introduced, so that it's obvious that it's benign. Test Plan: ./validate Reviewers: simonpj, austin, bgamari Subscribers: thomie, simonmar Differential Revision: https://phabricator.haskell.org/D2390 GHC Trac Issues: #4012 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 5 16:42:52 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 05 Jul 2016 16:42:52 -0000 Subject: [GHC] #12171: option to accept ISO C99... unsupported In-Reply-To: <047.3422b3804ba7edffe1760a7d3448370f@haskell.org> References: <047.3422b3804ba7edffe1760a7d3448370f@haskell.org> Message-ID: <062.32658f79fe967c25be8823f35743ec6d@haskell.org> #12171: option to accept ISO C99... unsupported ----------------------------------------+----------------------------- Reporter: wozgonon | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Build System | Version: 8.0.1 Resolution: | Keywords: Operating System: Windows | Architecture: x86 Type of failure: Building GHC failed | Test Case: Blocked By: | Blocking: Related Tickets: #11005 | Differential Rev(s): Wiki Page: | ----------------------------------------+----------------------------- Changes (by thomie): * related: => #11005 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 5 16:45:26 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 05 Jul 2016 16:45:26 -0000 Subject: [GHC] #12227: regression: out of memory with -O2 -ddump-hi on a complex INLINE function In-Reply-To: <046.5eb6cdc259c89a5a386fca350cf30507@haskell.org> References: <046.5eb6cdc259c89a5a386fca350cf30507@haskell.org> Message-ID: <061.66253947d953a6f382d53939449270cd@haskell.org> #12227: regression: out of memory with -O2 -ddump-hi on a complex INLINE function -------------------------------------+------------------------------------- Reporter: j6carey | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 (CodeGen) | 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 simonpj): I've learned a bit about this example. 1. It builds big, deeply-nested coercions. 2. The actual memory exhaustion comes from the pretty printer. Here's a dump from `-ticky` of GHC itself, with the `-ddump-hi` on: {{{ Entries Alloc Alloc'd Non-void Arguments STG Name -------------------------------------------------------------------------------- 24320676 1066014032 0 4 MEiM $waboveNest{v rb81} (ghc-8.1:Pretty) (fun) 19400250 621778256 0 3 MEM beside{v r16q} (ghc-8.1:Pretty) (fun) 2773145 143762232 0 4 EMiL ghc-8.1:Pretty.$wsep1{v rb7d} (fun) 3466978 117540632 0 2 >L base-4.9.0.0:GHC.Base.map{v 01X} (fun) 4143110 114461032 0 1 M oneLiner{v r16K} (ghc-8.1:Pretty) (fun) 1939310 97813720 0 1 M ghc-8.1:Coercion.coercionKind_go{v rrbv} (fun) 1475028 66514184 0 3 i.M containers-0.5.7.1 at containers-0.5.7.1:Data.IntMap.Base.$winsert{v rnBj} (fun) 902398 65925152 0 2 LL ghc-8.1:Util.$wsplitAtList{v rhOj} (fun) }}} So clearly the pretty printer is behaving very badly when given deeply nested things to print. 3. Aside from that, a tremendous amount of time is spent in `coercionKind`. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 5 16:48:05 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 05 Jul 2016 16:48:05 -0000 Subject: [GHC] #11385: Unify named wildcards in different type applications In-Reply-To: <051.0076b412916fb4cfc0823d8e3d44b32d@haskell.org> References: <051.0076b412916fb4cfc0823d8e3d44b32d@haskell.org> Message-ID: <066.6749c3a4f39c1088d9eff3727f5e37b4@haskell.org> #11385: Unify named wildcards in different type applications -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.1 checker) | Keywords: Resolution: | NamedWildCards 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 Iceland_jack): I disliked the lack of binders in my idea. That would be fixed by Replying to [comment:2 goldfire]: > {{{ > asTypeOf = \ @a -> const @a @a > }}} like comment:4:ticket:11350 and comment:1:ticket:11638. Let me see if I understand: {{{#!hs add4 :: (Enum a, Enum b) => a -> b -> Int add4 a b = (fromEnum a + fromEnum b) `mod` 4 }}} if you want `add4 :: Enum a => a -> a -> Int` you write {{{#!hs -- add4 @_a @_a` \ @a -> add4 @a @a :: Enum a => a -> a -> Int }}} {{{#!hs -- Sub @(Ord _a) @(Eq _a) \ @a -> Sub @(Ord a) @(Eq a) :: (Ord a => Dict (Eq a)) -> Ord a :- Eq a }}} {{{#!hs -- map @_a @_a \ @a -> map @a @a :: (a -> a) -> [a] -> [a] }}} LGTM. ---- It may be worth allowing {{{#!hs (\ @a -> map @a @a) @Int :: (Int -> Int) -> [Int] -> [Int] }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 5 16:48:17 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 05 Jul 2016 16:48:17 -0000 Subject: [GHC] #4012: Compilation results are not deterministic In-Reply-To: <043.9c3dc141e8901acb12e4d7c1e6038096@haskell.org> References: <043.9c3dc141e8901acb12e4d7c1e6038096@haskell.org> Message-ID: <058.a4ca216fad33af633c4a94a0816e316d@haskell.org> #4012: Compilation results are not deterministic -------------------------------------+------------------------------------- Reporter: kili | Owner: niteria Type: bug | Status: new Priority: high | Milestone: 8.2.1 Component: Compiler | Version: 6.12.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Other | Test Case: Blocked By: 11362 | Blocking: 12262 Related Tickets: #10424 | Differential Rev(s): Phab:D910, | Phab:D1073, Phab:D1133, Phab:D1192, | Phab:D1268, Phab:D1360, Phab:D1373, Wiki Page: | Phab:D1396, Phab:D1457, Phab:D1468, DeterministicBuilds | Phab:D1487, Phab:D1504, Phab:D1508 -------------------------------------+------------------------------------- Comment (by Bartosz Nitka ): In [changeset:"1b058d4a0f4b12bf15d186409cfff8a2b93fd3a9/ghc" 1b058d4/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="1b058d4a0f4b12bf15d186409cfff8a2b93fd3a9" Remove varEnvElts varEnvElts can introduce unnecessary nondeterminism and we can finally remove it, so that no one will use it by accident. If someone wants to use varEnvElts they should either use DVarEnv or use nonDetEltsUFM and document why it doesn't introduce nondeterminism. GHC Trac: #4012 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 5 16:50:59 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 05 Jul 2016 16:50:59 -0000 Subject: [GHC] #12227: regression: out of memory with -O2 -ddump-hi on a complex INLINE function In-Reply-To: <046.5eb6cdc259c89a5a386fca350cf30507@haskell.org> References: <046.5eb6cdc259c89a5a386fca350cf30507@haskell.org> Message-ID: <061.6fb4feccee500c03dbabe7bee5793ba0@haskell.org> #12227: regression: out of memory with -O2 -ddump-hi on a complex INLINE function -------------------------------------+------------------------------------- Reporter: j6carey | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 (CodeGen) | 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 thomie): The pretty pinter issue might be the same issue as https://github.com/haskell/pretty/issues/32. I can have a look later this week. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 5 16:54:23 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 05 Jul 2016 16:54:23 -0000 Subject: [GHC] #11385: Unify named wildcards in different type applications In-Reply-To: <051.0076b412916fb4cfc0823d8e3d44b32d@haskell.org> References: <051.0076b412916fb4cfc0823d8e3d44b32d@haskell.org> Message-ID: <066.da1c9e91f969c44ab5aca88742beca7b@haskell.org> #11385: Unify named wildcards in different type applications -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.1 checker) | Keywords: Resolution: | NamedWildCards 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 Iceland_jack): Continuing with ticket comment:4:ticket:11350, these make sense to me {{{#!hs asTypeOf @a = const @a @a endomap @a = fmap @[] @a @a }}} but wait, `asTypeOf @a` × `endomap @a` bind a new type variable. How does that mesh with your intuition from comment:9:ticket:11350? {{{#!hs asTypeOf = \ @a -> const @a @a -- vs asTypeOf @a = const @a @a }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 5 17:00:55 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 05 Jul 2016 17:00:55 -0000 Subject: [GHC] #12358: Read1/Read2 don't have methods defined in terms of ReadPrec In-Reply-To: <050.f17a87cdce0c0bbe442c6db7afeec481@haskell.org> References: <050.f17a87cdce0c0bbe442c6db7afeec481@haskell.org> Message-ID: <065.6d5f312f082667b79f2f3031918428b5@haskell.org> #12358: Read1/Read2 don't have methods defined in terms of ReadPrec -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: feature request | Status: patch Priority: normal | Milestone: 8.2.1 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): Phab:D2379 Wiki Page: | -------------------------------------+------------------------------------- Comment (by ekmett): Makes sense to me. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 5 17:04:42 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 05 Jul 2016 17:04:42 -0000 Subject: [GHC] #12358: Read1/Read2 don't have methods defined in terms of ReadPrec In-Reply-To: <050.f17a87cdce0c0bbe442c6db7afeec481@haskell.org> References: <050.f17a87cdce0c0bbe442c6db7afeec481@haskell.org> Message-ID: <065.416fc8f2c1ae6a7b2f1753bfb73c8566@haskell.org> #12358: Read1/Read2 don't have methods defined in terms of ReadPrec -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: feature request | Status: patch Priority: normal | Milestone: 8.2.1 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): Phab:D2379 Wiki Page: | -------------------------------------+------------------------------------- Comment (by ekmett): Regarding the committee: Ryan joined the committee back in January or so. I like to think of him as our "backwards compatibility specialist." Neil Mitchell joined around the same time. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 5 17:57:01 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 05 Jul 2016 17:57:01 -0000 Subject: [GHC] #11385: Unify named wildcards in different type applications In-Reply-To: <051.0076b412916fb4cfc0823d8e3d44b32d@haskell.org> References: <051.0076b412916fb4cfc0823d8e3d44b32d@haskell.org> Message-ID: <066.0b7edf8e6bfda2bd937e6367a18d3603@haskell.org> #11385: Unify named wildcards in different type applications -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.1 checker) | Keywords: Resolution: | NamedWildCards 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 goldfire): I'm assuming your `:: ...` in comment:3 are meant to be inferred, not part of what the user writes. Then yes. And your final example in comment:3 should most certainly be allowed; if it's not, we've designed the thing very wrongly. And I agree with all your examples in comment:4 except, possibly, the last. But it's probably just simpler to accept the last example along with the others. How does this contrast with comment:9:ticket:11350? These are top-level, whereas those are in an instance declaration. I think it's reasonable to have slightly different behavior. In both cases, the function body is interpreted with respect to the user-written type signature for the function. It's just that, in the instance case, the user-written type signature isn't really the full story. But I think it's all OK. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 5 17:59:10 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 05 Jul 2016 17:59:10 -0000 Subject: [GHC] #12181: Multi-threaded code on ARM64 GHC runtime doesn't use all available cores In-Reply-To: <045.62ec1d1031a2707c97a15db7c0ee2c82@haskell.org> References: <045.62ec1d1031a2707c97a15db7c0ee2c82@haskell.org> Message-ID: <060.6ce828cb1ce97cdf6e5eef197718c4a0@haskell.org> #12181: Multi-threaded code on ARM64 GHC runtime doesn't use all available cores --------------------------------------------+------------------------------ Reporter: varosi | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Runtime System | Version: 7.10.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: arm Type of failure: Runtime performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | --------------------------------------------+------------------------------ Comment (by thomie): varosi: you are reporting an issue with `+RTS -N`, correct? When compiling the following program with `-threaded`, and running it with `./Main +RTS -N`, it prints `2` instead of `4` on your machine: {{{ import Control.Concurrent main = getNumCapabilities >>= print }}} Here's the code that gets the number of processors when using `+RTS -N`, from `rts/posix/OSThreads.c`: {{{#!C uint32_t getNumberOfProcessors (void) { static uint32_t nproc = 0; if (nproc == 0) { #if defined(HAVE_SYSCONF) && defined(_SC_NPROCESSORS_ONLN) nproc = sysconf(_SC_NPROCESSORS_ONLN); #elif defined(HAVE_SYSCONF) && defined(_SC_NPROCESSORS_CONF) nproc = sysconf(_SC_NPROCESSORS_CONF); #elif defined(darwin_HOST_OS) size_t size = sizeof(uint32_t); if(sysctlbyname("hw.logicalcpu",&nproc,&size,NULL,0) != 0) { if(sysctlbyname("hw.ncpu",&nproc,&size,NULL,0) != 0) nproc = 1; } #elif defined(freebsd_HOST_OS) size_t size = sizeof(uint32_t); if(sysctlbyname("hw.ncpu",&nproc,&size,NULL,0) != 0) nproc = 1; #else nproc = 1; #endif } return nproc; } }}} From `man sysconf`: {{{ - _SC_NPROCESSORS_CONF The number of processors configured. - _SC_NPROCESSORS_ONLN The number of processors currently online (available). }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 5 18:12:53 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 05 Jul 2016 18:12:53 -0000 Subject: [GHC] #12195: RTS GetTime.c is broken on Darwins that include clock_gettime In-Reply-To: <049.daef56b071de7a0b4dee3129f5dcf900@haskell.org> References: <049.daef56b071de7a0b4dee3129f5dcf900@haskell.org> Message-ID: <064.e944d59a73137e4e67781b2f9251ffd9@haskell.org> #12195: RTS GetTime.c is broken on Darwins that include clock_gettime -------------------------------------+------------------------------------- Reporter: mistydemeo | Owner: Type: bug | Status: patch Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 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: | -------------------------------------+------------------------------------- Changes (by thomie): * cc: bgamari (added) * status: new => patch -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 5 18:14:10 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 05 Jul 2016 18:14:10 -0000 Subject: [GHC] #12366: Use TypeOperators for pattern synonyms? Message-ID: <049.e4107eacf0ef1bfeb4037f3fd29bbf88@haskell.org> #12366: Use TypeOperators for pattern synonyms? -------------------------------------+------------------------------------- Reporter: dubiousjim | Owner: Type: feature | Status: new request | Priority: low | Milestone: 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: -------------------------------------+------------------------------------- With the language setting `-XTypeOperators`, I can use ''varsym'' expressions, like `<|`, as type constructors. I would expect that we would then also be able to use them as pattern synonyms; but we can't. This is a request for that to become possible. {{{#!hs {-# LANGUAGE TypeOperators, PatternSynonyms #-} module Main where pattern (<|) x xs = Just (x, xs) main = case Just (1, [2,3]) of { Nothing -> putStrLn "Nothing"; y <| ys -> print y } }}} gives a parse error. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 5 18:21:15 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 05 Jul 2016 18:21:15 -0000 Subject: [GHC] #12195: RTS GetTime.c is broken on Darwins that include clock_gettime In-Reply-To: <049.daef56b071de7a0b4dee3129f5dcf900@haskell.org> References: <049.daef56b071de7a0b4dee3129f5dcf900@haskell.org> Message-ID: <064.7a48c87d9fe8f0b598a8a2543bf5e9a2@haskell.org> #12195: RTS GetTime.c is broken on Darwins that include clock_gettime -------------------------------------+------------------------------------- Reporter: mistydemeo | Owner: Type: bug | Status: patch Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 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): Thanks for the ping Thomie! -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 5 18:21:37 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 05 Jul 2016 18:21:37 -0000 Subject: [GHC] #11385: Unify named wildcards in different type applications In-Reply-To: <051.0076b412916fb4cfc0823d8e3d44b32d@haskell.org> References: <051.0076b412916fb4cfc0823d8e3d44b32d@haskell.org> Message-ID: <066.5acafc934b6bc6836239896f5b891661@haskell.org> #11385: Unify named wildcards in different type applications -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.1 checker) | Keywords: Resolution: | NamedWildCards 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 Iceland_jack): Replying to [comment:5 goldfire]: > I'm assuming your `:: ...` in comment:3 are meant to be inferred, not part of what the user writes. Yes Replying to [comment:5 goldfire]: > Then yes. And your final example in comment:3 should most certainly be allowed; ... > > And I agree with all your examples in comment:4 except, possibly, the last. But it's probably just simpler to accept the last example along with the others. > > ... But I think it's all OK. Great! -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 5 18:21:50 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 05 Jul 2016 18:21:50 -0000 Subject: [GHC] #12195: RTS GetTime.c is broken on Darwins that include clock_gettime In-Reply-To: <049.daef56b071de7a0b4dee3129f5dcf900@haskell.org> References: <049.daef56b071de7a0b4dee3129f5dcf900@haskell.org> Message-ID: <064.0393602b9cbb764dd604d4fdc374d282@haskell.org> #12195: RTS GetTime.c is broken on Darwins that include clock_gettime -------------------------------------+------------------------------------- Reporter: mistydemeo | Owner: Type: bug | Status: patch Priority: normal | Milestone: 8.0.2 Component: Compiler | Version: 8.0.1 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: | -------------------------------------+------------------------------------- Changes (by bgamari): * milestone: => 8.0.2 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 5 18:25:17 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 05 Jul 2016 18:25:17 -0000 Subject: [GHC] #12366: Use TypeOperators for pattern synonyms? In-Reply-To: <049.e4107eacf0ef1bfeb4037f3fd29bbf88@haskell.org> References: <049.e4107eacf0ef1bfeb4037f3fd29bbf88@haskell.org> Message-ID: <064.978c7cac4c1bb7dc3fbcfd062b368dfc@haskell.org> #12366: Use TypeOperators for pattern synonyms? -------------------------------------+------------------------------------- Reporter: dubiousjim | Owner: Type: feature request | Status: new Priority: low | Milestone: Component: Compiler | Version: 8.0.1 (Parser) | 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): Unfortunately, I don't think this is possible. The type-level namespace and the term-level namespace are organized differently: `|>` in a type is indeed like a capitalized word, but `|>` in a term is like a lowercase word. The problem is, as I understand it, that the parser needs to be able to know where the constructors/pattern synonyms are in a pattern. Is `C (|>)` binding the variable `|>` or are we matching against a nullary pattern synonym `|>`? It's impossible to tell. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 5 18:25:21 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 05 Jul 2016 18:25:21 -0000 Subject: [GHC] #12195: RTS GetTime.c is broken on Darwins that include clock_gettime In-Reply-To: <049.daef56b071de7a0b4dee3129f5dcf900@haskell.org> References: <049.daef56b071de7a0b4dee3129f5dcf900@haskell.org> Message-ID: <064.01206b6717afd0c746ba4b492c0f58dd@haskell.org> #12195: RTS GetTime.c is broken on Darwins that include clock_gettime -------------------------------------+------------------------------------- Reporter: mistydemeo | Owner: Type: bug | Status: patch Priority: normal | Milestone: 8.0.2 Component: Compiler | Version: 8.0.1 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): The patch looks reasonable to me. I'll go ahead and merge it. Thanks mistydemeo! -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 5 18:28:06 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 05 Jul 2016 18:28:06 -0000 Subject: [GHC] #12181: Multi-threaded code on ARM64 GHC runtime doesn't use all available cores In-Reply-To: <045.62ec1d1031a2707c97a15db7c0ee2c82@haskell.org> References: <045.62ec1d1031a2707c97a15db7c0ee2c82@haskell.org> Message-ID: <060.d243be70b2e95332ad85f4f8a7052877@haskell.org> #12181: Multi-threaded code on ARM64 GHC runtime doesn't use all available cores --------------------------------------------+------------------------------ Reporter: varosi | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Runtime System | Version: 7.10.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: arm Type of failure: Runtime performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | --------------------------------------------+------------------------------ Comment (by rwbarton): It really doesn't seem sensible to me to have GHC assume by default that CPUs that are off-line will magically become available under load. Though admittedly I don't know what the use of taking CPUs off-line is supposed to be. This seems like a deficiency in the operating system, that there isn't a way to ask it "how many CPUs will my program run on". It's not for GHC to work around this I think. You could do so yourself by starting a thread that periodically checks the number of currently available processors and calls `setNumCapabilities`. Or just run with `-N4`. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 5 18:55:52 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 05 Jul 2016 18:55:52 -0000 Subject: [GHC] #12200: ghc-pkg check complains about missing libCffi on dynamic-only install In-Reply-To: <047.19d6daf299749c7e52d2286f36cb4814@haskell.org> References: <047.19d6daf299749c7e52d2286f36cb4814@haskell.org> Message-ID: <062.2d993a1fc63ca9fd1c35e72799f664fd@haskell.org> #12200: ghc-pkg check complains about missing libCffi on dynamic-only install -------------------------------------+------------------------------------- Reporter: dudebout | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: ghc-pkg | Version: 7.10.2 Resolution: | Keywords: libCffi 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 thomie): Commit b30015e78db99d79cdb48c6c810e3fd49573c5cd is relevant: {{{ Author: Ian Lynagh Date: Sat Mar 23 23:55:56 2013 +0000 Change how we handle libffi I think overall the new approach is simpler. Rather than unpacking the libffi.a and putting the .o files into our libHSrts.a, we just use the libffi.a. This change also means that when compiling programs for the dyn way, they get explicitly linked against libffi.so (rather than relying on librts.so being linked against it). This might fix a problem on FreeBSD, where programs cannot find libffi.so. }}} In `compiler/main/Packages.hs`: {{{ -- For non-Haskell libraries, we use the name "Cfoo". The .a -- file is libCfoo.a, and the .so is libfoo.so. That way the -- linker knows what we mean for the vanilla (-lCfoo) and dyn -- (-lfoo) ways. We therefore need to strip the 'C' off here. }}} I don't know why in `rts/package.conf.in`, `FFI_LIB` is listed in `hs- libraries`. It isn't a Haskell library, but because of its listing there, this code in `utils/ghc-pkg/Main.hs` is triggered: {{{ checkHSLib :: Verbosity -> [String] -> String -> Validate () checkHSLib _verbosity dirs lib = do let filenames = ["lib" ++ lib ++ ".a", "lib" ++ lib ++ ".p_a", "lib" ++ lib ++ "-ghc" ++ Version.version ++ ".so", "lib" ++ lib ++ "-ghc" ++ Version.version ++ ".dylib", lib ++ "-ghc" ++ Version.version ++ ".dll"] b <- liftIO $ doesFileExistOnPath filenames dirs when (not b) $ verror ForceFiles ("cannot find any of " ++ show filenames ++ " on library path") }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 5 19:02:47 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 05 Jul 2016 19:02:47 -0000 Subject: [GHC] #4012: Compilation results are not deterministic In-Reply-To: <043.9c3dc141e8901acb12e4d7c1e6038096@haskell.org> References: <043.9c3dc141e8901acb12e4d7c1e6038096@haskell.org> Message-ID: <058.cd2f9f9a6a326fcb2185348912b9c5e9@haskell.org> #4012: Compilation results are not deterministic -------------------------------------+------------------------------------- Reporter: kili | Owner: niteria Type: bug | Status: new Priority: high | Milestone: 8.2.1 Component: Compiler | Version: 6.12.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Other | Test Case: Blocked By: 11362 | Blocking: 12262 Related Tickets: #10424 | Differential Rev(s): Phab:D910, | Phab:D1073, Phab:D1133, Phab:D1192, | Phab:D1268, Phab:D1360, Phab:D1373, Wiki Page: | Phab:D1396, Phab:D1457, Phab:D1468, DeterministicBuilds | Phab:D1487, Phab:D1504, Phab:D1508 -------------------------------------+------------------------------------- Changes (by meteficha): * cc: felipe.lessa@… (removed) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 5 19:58:53 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 05 Jul 2016 19:58:53 -0000 Subject: [GHC] #12227: regression: out of memory with -O2 -ddump-hi on a complex INLINE function In-Reply-To: <046.5eb6cdc259c89a5a386fca350cf30507@haskell.org> References: <046.5eb6cdc259c89a5a386fca350cf30507@haskell.org> Message-ID: <061.d8c29eeef53866041c3f45c571705254@haskell.org> #12227: regression: out of memory with -O2 -ddump-hi on a complex INLINE function -------------------------------------+------------------------------------- Reporter: j6carey | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 (CodeGen) | 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 simonpj): Sounds very similar. Thanks for taking a look. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 5 20:08:58 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 05 Jul 2016 20:08:58 -0000 Subject: [GHC] #12195: RTS GetTime.c is broken on Darwins that include clock_gettime In-Reply-To: <049.daef56b071de7a0b4dee3129f5dcf900@haskell.org> References: <049.daef56b071de7a0b4dee3129f5dcf900@haskell.org> Message-ID: <064.66e2a9fab82979a4a12218d99e753e6e@haskell.org> #12195: RTS GetTime.c is broken on Darwins that include clock_gettime -------------------------------------+------------------------------------- Reporter: mistydemeo | Owner: Type: bug | Status: patch Priority: normal | Milestone: 8.0.2 Component: Compiler | Version: 8.0.1 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 Ben Gamari ): In [changeset:"b7b130c5102948b38aaba723044288e16a80d492/ghc" b7b130c/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="b7b130c5102948b38aaba723044288e16a80d492" Fix GetTime.c on Darwin with clock_gettime On Darwin versions with clock_gettime, #ifdefs will prevent the mach-specific time functions from being used in most places, and the mach time headers won't be included; however, this section was guarded incorrectly and would still try to use them. Fixes #12195. }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 5 20:09:48 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 05 Jul 2016 20:09:48 -0000 Subject: [GHC] #12195: RTS GetTime.c is broken on Darwins that include clock_gettime In-Reply-To: <049.daef56b071de7a0b4dee3129f5dcf900@haskell.org> References: <049.daef56b071de7a0b4dee3129f5dcf900@haskell.org> Message-ID: <064.b5182bfa63635333b352f76d1408961a@haskell.org> #12195: RTS GetTime.c is broken on Darwins that include clock_gettime -------------------------------------+------------------------------------- Reporter: mistydemeo | Owner: Type: bug | Status: merge Priority: normal | Milestone: 8.0.2 Component: Compiler | Version: 8.0.1 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: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: patch => merge -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 5 20:10:05 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 05 Jul 2016 20:10:05 -0000 Subject: [GHC] #12366: Use TypeOperators for pattern synonyms? In-Reply-To: <049.e4107eacf0ef1bfeb4037f3fd29bbf88@haskell.org> References: <049.e4107eacf0ef1bfeb4037f3fd29bbf88@haskell.org> Message-ID: <064.dfcfda8c9ab4fdd6440f0cb4a7dbb758@haskell.org> #12366: Use TypeOperators for pattern synonyms? -------------------------------------+------------------------------------- Reporter: dubiousjim | Owner: Type: feature request | Status: closed Priority: low | Milestone: Component: Compiler | Version: 8.0.1 (Parser) | Keywords: Resolution: invalid | 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 mpickering): * keywords: => PatternSynonyms * status: new => closed * resolution: => invalid Comment: Pattern synonym names live in the data constructor name space whilst the type operators extension only affects type constructors. Pattern synonym definitions define no type construction so there shouldn't be any interaction between the two features. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 5 22:47:43 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 05 Jul 2016 22:47:43 -0000 Subject: [GHC] #12366: Use TypeOperators for pattern synonyms? In-Reply-To: <049.e4107eacf0ef1bfeb4037f3fd29bbf88@haskell.org> References: <049.e4107eacf0ef1bfeb4037f3fd29bbf88@haskell.org> Message-ID: <064.6bacf19616714d4ddb3e2bbb8252e014@haskell.org> #12366: Use TypeOperators for pattern synonyms? -------------------------------------+------------------------------------- Reporter: dubiousjim | Owner: Type: feature request | Status: closed Priority: low | Milestone: Component: Compiler | Version: 8.0.1 (Parser) | Keywords: Resolution: invalid | 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 dubiousjim): Ok, thanks for the prompt and clear explanation. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 6 03:01:16 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 06 Jul 2016 03:01:16 -0000 Subject: [GHC] #12240: Common Sense for Type Classes In-Reply-To: <050.3dcf7ad3ce6a480cdc5fe8435e755275@haskell.org> References: <050.3dcf7ad3ce6a480cdc5fe8435e755275@haskell.org> Message-ID: <065.8a8028b5a577ff5f34d229be1f1b17d7@haskell.org> #12240: Common Sense for Type Classes -------------------------------------+------------------------------------- Reporter: Mathnerd314 | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 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 Mathnerd314): Replying to [comment:8 goldfire]: > 1. You can already do what you want, if you rephrase your instance. From the initial post: > > {{{#!hs > instance (a ~ Int, b ~ Char) => C a b where ... > }}} > Sure, this works for the original, and the original can also be solved with functional dependencies (as in comment:3). Even the example in comment:4 could be done with equality constraints, `(a ~ Int) => instance C a Bool` and so on. The issue is the open-world problem; with such general instance heads, you cannot extend the class to have more instances without running into overlap problems. Whereas with my approach, instances can still be declared; they just mean that instance resolution will fail more often (which is already an expected side-effect of declaring instances). From what I can tell, there was no reason for the matching (instead of unifying) behavior to begin with; it was just "how type class matching worked", back in 1996. E.g. page 12 of https://courses.cs.washington.edu/courses/cse590p/06sp/multi.pdf mentions that matching uses one-way unification, but gives no explanation of why two-way unification was not chosen. Then on page 13 they state that constraints can be improved if they unify with a unique instance, but just say "it is not yet clear if it would improve enough useful programs to be worth the extra effort." > Phabricator has well-written reasons why; see "Rejecting patches" on [https://secure.phabricator.com/book/phabcontrib/article/contributing_code/ this page]. "The Phabricator upstream is Phacility, Inc. We maintain total control over the project and roadmap. There is no democratic process, voting, or community-driven decision making. This model is better at some things and worse at others than a more community-focused model would be, but it is the model we operate under." I am not sure this describes GHC well; wiki:TeamGHC states "GHC's development as a whole is not led by any particular group, company, or individual." > At the moment, the original poster has gotten other member of the community to say that they wouldn't actively block the implementation of your idea; I'm afraid this is hardly a ringing endorsement. My impression is that this is better than the reaction to other (implemented!) proposals, e.g. Foldable in the Prelude, which were actively opposed. This issue is a rather small, dark corner of the language, so few have the patience to discuss it. Furthermore, I have not really elaborated on my proposal, because I don't know enough of GHC internals to describe it accurately, so it is hard to actively support a nebulous concept. At least a patch can be judged on its merits. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 6 03:08:07 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 06 Jul 2016 03:08:07 -0000 Subject: [GHC] #12360: Extend support for binding implicit parameters In-Reply-To: <051.60aab356d30170c681e545a4ae0a0e84@haskell.org> References: <051.60aab356d30170c681e545a4ae0a0e84@haskell.org> Message-ID: <066.d03f05c6a4872c70555bba08a399bb95@haskell.org> #12360: Extend support for binding implicit parameters -------------------------------------+------------------------------------- Reporter: MichaelBurge | Owner: 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: | -------------------------------------+------------------------------------- Comment (by MichaelBurge): I use implicit parameters a lot in my larger programs, and pattern-binding seems like a fundamental feature. Usually I set them in a top-level function for configuration files or similar, where the workaround in this ticket isn't too inconvenient. I did have one creative use that I thought would be confusing without this feature: {{{ {-# LANGUAGE ImplicitParams,RankNTypes #-} type UserId = Int data UserLoggedIn = UserLoggedIn UserId newtype Authorized a = Authorized a class Authorizable a where authorize :: a -> IO (Authorized a) instance Authorizable UserLoggedIn where authorize userId = undefined -- Imagine checking the user's cookies or the database or something fetchLatestUnreadMessage :: (?u :: Authorized UserLoggedIn) => IO (Maybe String) fetchLatestUnreadMessage = undefined -- No need to check authentication; the fact that we have an Authorized UserLoggedIn means the user has already been authenticated. type WebsitePage = String showUserHomepage :: IO WebsitePage showUserHomepage = do -- u <- authorize $ UserLoggedIn undefined -- let ?u = u mMessage <- fetchLatestUnreadMessage case mMessage of Nothing -> return "" Just message -> return message main = do homepage <- showUserHomepage putStrLn homepage }}} In this example, the idea is based on the common pattern of requiring the user to retrieve a token from your API before he can call any of the other functions. Sometimes it is annoying to keep the token around, since its only use is to enforce the order that you call functions in. By hiding the token in an implicit variable, we get a type error if you don't authorize yourself before executing an action requiring authorization. The example code gives a compile error, but uncommenting the 2 lines will cause it to succeed. I thought it would be confusing to have 2 such tokens in scope(u and ?u), so I opted not to use this design. Looking in my project, here are the only other uses of implicit parameters: * Break module dependencies(if f depends on g and g depends on f and they are in different modules, make g depend on ?f and break the dependency in a top-level module by assigning ?f = f. * Read configuration files at the start. This also happens in a top-level module. * I use the new (?c :: CallStack) feature for ease-of-debugging. I don't see much code on Hackage using implicit parameters, and they're not as useful on smaller projects. But they certainly do see some use. And I will probably continue to find new uses for them, where this pattern- binding feature could help. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 6 03:24:55 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 06 Jul 2016 03:24:55 -0000 Subject: [GHC] #12360: Extend support for binding implicit parameters In-Reply-To: <051.60aab356d30170c681e545a4ae0a0e84@haskell.org> References: <051.60aab356d30170c681e545a4ae0a0e84@haskell.org> Message-ID: <066.dd1b42d8113c30113f0191622a5a9cab@haskell.org> #12360: Extend support for binding implicit parameters -------------------------------------+------------------------------------- Reporter: MichaelBurge | Owner: 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: | -------------------------------------+------------------------------------- Comment (by Iceland_jack): This is a bad idea right: {{{#!hs pattern ImplicitTime :: (?t::UTCTime) => UTCTime pattern ImplicitTime = ?t printTime :: (?t :: UTCTime) => IO () printTime = putStrLn $ show ImplicitTime main = do ImplicitTime <- getCurrentTime printTime }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 6 03:37:56 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 06 Jul 2016 03:37:56 -0000 Subject: [GHC] #12240: Common Sense for Type Classes In-Reply-To: <050.3dcf7ad3ce6a480cdc5fe8435e755275@haskell.org> References: <050.3dcf7ad3ce6a480cdc5fe8435e755275@haskell.org> Message-ID: <065.8e91e68ff7e56f870e6c697740628671@haskell.org> #12240: Common Sense for Type Classes -------------------------------------+------------------------------------- Reporter: Mathnerd314 | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 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 rwbarton): > It is a blatant violation of the Haskell Report ("A type may not be declared as an instance of a particular class more than once in the program."), yet it compiles in GHC with no extensions. Yes, so it is a bug. See #2356. > Meanwhile, all I want to do is relax instantiation from "a single instance matches and no other instance unifies" to "a single instance unifies and no other instance unifies". This is only interesting in limited situations, such as the example in comment:4, and leaves all Haskell 98 instances unchanged. I do not see how it adds any incoherence, because in both rules only a single instance is allowed. Your proposal seems to even allow situations like {{{#!hs class C a b where f :: a -> Int instance C String () where f _ = 1 instance C String Bool where f _ = 2 }}} If the two instances are in different modules, the expression `f "a" :: Int` will type check but have value `1` or `2` depending on which module is imported. Yet the instances are not even overlapping. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 6 03:51:14 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 06 Jul 2016 03:51:14 -0000 Subject: =?utf-8?q?Re=3A_=5BGHC=5D_=2311632=3A_Data=2EChar_repeated_readL?= =?utf-8?q?itChar_barfs_on_output_from_show_=22=C3=B31=22?= In-Reply-To: <049.9bf2436e7fb9c211d83d1b0ba3c6ee23@haskell.org> References: <049.9bf2436e7fb9c211d83d1b0ba3c6ee23@haskell.org> Message-ID: <064.a1cc08fbe591a00e6228ee98f92d10b6@haskell.org> #11632: Data.Char repeated readLitChar barfs on output from show "ó1" -------------------------------------+------------------------------------- Reporter: inversemot | Owner: kgupta Type: bug | Status: new Priority: normal | Milestone: Component: libraries/base | Version: 7.10.3 Resolution: | Keywords: newcomer Operating System: Linux | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by kgupta): I think for option 2 you meant "consume the `\\&`", right? Because the `1` isn't part of the null character? Or am I misinterpreting? Thanks for your patience. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 6 07:36:46 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 06 Jul 2016 07:36:46 -0000 Subject: [GHC] #12240: Common Sense for Type Classes In-Reply-To: <050.3dcf7ad3ce6a480cdc5fe8435e755275@haskell.org> References: <050.3dcf7ad3ce6a480cdc5fe8435e755275@haskell.org> Message-ID: <065.e4d24680bc4df299d5770f8d5019bbf4@haskell.org> #12240: Common Sense for Type Classes -------------------------------------+------------------------------------- Reporter: Mathnerd314 | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 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 adamgundry): > From what I can tell, there was no reason for the matching (instead of unifying) behavior to begin with; it was just "how type class matching worked", back in 1996. E.g. page 12 of ​https://courses.cs.washington.edu/courses/cse590p/06sp/multi.pdf mentions that matching uses one-way unification, but gives no explanation of why two-way unification was not chosen. Then on page 13 they state that constraints can be improved if they unify with a unique instance, but just say "it is not yet clear if it would improve enough useful programs to be worth the extra effort." I believe the reason is the open world assumption, i.e. allowing for instances to be added later without changing the solver behaviour. Also, it's not clear to me whether any theoretical properties have been studied for the type system with unification in place of matching. Note one of the conditions regarding Decision 8 on page 13 of the paper you cite (my emphasis): > * //no matter what other (legal) instance declarations are added//, there is only one instance declaration that the constraint can be made to match in this way. This is much more restrictive than your proposal, and would indeed not apply to many programs (if any), so it indeed hardly seems worth it. > This issue is a rather small, dark corner of the language, so few have the patience to discuss it. I respectfully disagree. You are suggesting a rather significant change to the type system, and I for one think it is very interesting to discuss its implications. Thank you for bringing it up! Please take all these comments in a spirit of constructive debate, and apologies if my previous comment was too blunt. > Furthermore, I have not really elaborated on my proposal, because I don't know enough of GHC internals to describe it accurately, so it is hard to actively support a nebulous concept. At least a patch can be judged on its merits. Most people won't judge a patch at all, I'm afraid. ;-) We really need a clear specification of the feature, articulated independently of the details of the implementation. A wiki page is a good place to put this, and can link to this ticket and other discussions. A specification should outline the motivation for the feature, describe the changes to the type system (not just the type inference algorithm, although that may be helpful too), give plenty of examples, and mention potential problems with the extension. On a different tangent, consider this module: {{{#!hs class C a where foo :: a instance C Int where foo = 42 f _ = foo }}} What is the inferred type of `f`? Previously it would have been `C a => b -> a` but under your proposal it would be `b -> Int`, right? This means that enabling the extension might cause existing programs to cease to type-check. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 6 08:43:14 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 06 Jul 2016 08:43:14 -0000 Subject: [GHC] #12367: Commit adding instances to GHC.Generics regression compiler performance Message-ID: <046.87a5f8a842934b4554eedf79fb6bebbc@haskell.org> #12367: Commit adding instances to GHC.Generics regression compiler performance -------------------------------------+------------------------------------- Reporter: bgamari | Owner: bgamari Type: bug | Status: new Priority: normal | Milestone: 8.0.2 Component: Compiler | Version: 8.0.1 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: -------------------------------------+------------------------------------- Recently 673efccb3b348e9daf23d9e65460691bbea8586e added a number of new instances for types defined in `GHC.Generics`. Unfortunately, it seems that this has regressed nofib compilation allocations (and also, it seems, compile time) by about 10%. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 6 09:37:30 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 06 Jul 2016 09:37:30 -0000 Subject: =?utf-8?q?Re=3A_=5BGHC=5D_=2311632=3A_Data=2EChar_repeated_readL?= =?utf-8?q?itChar_barfs_on_output_from_show_=22=C3=B31=22?= In-Reply-To: <049.9bf2436e7fb9c211d83d1b0ba3c6ee23@haskell.org> References: <049.9bf2436e7fb9c211d83d1b0ba3c6ee23@haskell.org> Message-ID: <064.f66b4cb5a233a5dfa2d96646ced0ec80@haskell.org> #11632: Data.Char repeated readLitChar barfs on output from show "ó1" -------------------------------------+------------------------------------- Reporter: inversemot | Owner: kgupta Type: bug | Status: new Priority: normal | Milestone: Component: libraries/base | Version: 7.10.3 Resolution: | Keywords: newcomer Operating System: Linux | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by thomie): Replying to [comment:9 kgupta]: > I think for option 2 you meant "consume the `\\&`", right? Yes, I updated comment:5. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 6 09:46:20 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 06 Jul 2016 09:46:20 -0000 Subject: [GHC] #11832: Allow reify to yield types in the current declaration group In-Reply-To: <056.c55a5c5fc06f6b4965766fc5bf61b445@haskell.org> References: <056.c55a5c5fc06f6b4965766fc5bf61b445@haskell.org> Message-ID: <071.e54719350ab7520b439d0b5aeb2bf296@haskell.org> #11832: Allow reify to yield types in the current declaration group -------------------------------------+------------------------------------- Reporter: | Owner: facundo.dominguez | facundo.dominguez Type: feature request | Status: patch Priority: normal | Milestone: Component: Template Haskell | Version: 7.10.3 Resolution: | Keywords: reify Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2286 Wiki Page: | TemplateHaskell/Reify | -------------------------------------+------------------------------------- Comment (by Facundo Domínguez ): In [changeset:"567dbd9bcb602accf3184b83050f2982cbb7758b/ghc" 567dbd9b/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="567dbd9bcb602accf3184b83050f2982cbb7758b" Have addModFinalizer expose the local type environment. Summary: This annotates the splice point with 'HsSpliced ref e' where 'e' is the result of the splice. 'ref' is a reference that the typechecker will fill with the local type environment. The finalizer then reads the ref and uses the local type environment, which causes 'reify' to find local variables when run in the finalizer. Test Plan: ./validate Reviewers: simonpj, simonmar, bgamari, austin, goldfire Reviewed By: goldfire Subscribers: simonmar, thomie, mboes Differential Revision: https://phabricator.haskell.org/D2286 GHC Trac Issues: #11832 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 6 09:49:57 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 06 Jul 2016 09:49:57 -0000 Subject: [GHC] #11832: Allow reify to yield types in the current declaration group In-Reply-To: <056.c55a5c5fc06f6b4965766fc5bf61b445@haskell.org> References: <056.c55a5c5fc06f6b4965766fc5bf61b445@haskell.org> Message-ID: <071.5bef815cb672f1f24e34d221f142c195@haskell.org> #11832: Allow reify to yield types in the current declaration group -------------------------------------+------------------------------------- Reporter: | Owner: facundo.dominguez | facundo.dominguez Type: feature request | Status: closed Priority: normal | Milestone: Component: Template Haskell | Version: 7.10.3 Resolution: fixed | Keywords: reify Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2286 Wiki Page: | TemplateHaskell/Reify | -------------------------------------+------------------------------------- Changes (by facundo.dominguez): * status: patch => closed * resolution: => fixed -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 6 10:04:45 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 06 Jul 2016 10:04:45 -0000 Subject: [GHC] #12367: Commit adding instances to GHC.Generics regression compiler performance In-Reply-To: <046.87a5f8a842934b4554eedf79fb6bebbc@haskell.org> References: <046.87a5f8a842934b4554eedf79fb6bebbc@haskell.org> Message-ID: <061.316349b3f38c9d7ef7f151fb11d0c116@haskell.org> #12367: Commit adding instances to GHC.Generics regression compiler performance -------------------------------------+------------------------------------- Reporter: bgamari | Owner: bgamari Type: bug | Status: new Priority: normal | Milestone: 8.0.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: | -------------------------------------+------------------------------------- @@ -4,1 +4,1 @@ - compile time) by about 10%. + compile time) by between 0 and 20% (on average about 5%). New description: Recently 673efccb3b348e9daf23d9e65460691bbea8586e added a number of new instances for types defined in `GHC.Generics`. Unfortunately, it seems that this has regressed nofib compilation allocations (and also, it seems, compile time) by between 0 and 20% (on average about 5%). -- Comment (by bgamari): ||= Test name =||= Absolute change =||= relative change =|| || compile-allocs/MyList || 20238384 || 0.208624775040415 || || compile-allocs/MyList || 20281496 || 0.206217801180845 || || compile-allocs/Prog || 20334192 || 0.202959317331712 || || compile-allocs/Prog || 20344656 || 0.20053198007393 || || compile-allocs/Basics || 22115840 || 0.185615422473695 || || compile-allocs/Basics || 22149816 || 0.183089910175923 || || compile-allocs/Assemble_loadvec || 20347184 || 0.166966893079396 || || compile-allocs/Digraph || 21606168 || 0.166243308385695 || || compile-allocs/Assemble_loadvec || 20357600 || 0.165346296105217 || || compile-allocs/Shows || 20296024 || 0.165204453781781 || || compile-allocs/Digraph || 21659944 || 0.165084805640568 || || compile-allocs/Shows || 20338616 || 0.163719820616552 || || compile-allocs/Tol_cal || 20737568 || 0.161829271665394 || || compile-allocs/Queue || 20579112 || 0.161181557853612 || || compile-allocs/Tol_cal || 20731568 || 0.160175008827888 || || compile-allocs/Queue || 20600368 || 0.159599282181737 || || compile-allocs/Vtslib || 20374904 || 0.155144898631996 || || compile-allocs/Match || 20975896 || 0.154183839207216 || || compile-allocs/Vtslib || 20368168 || 0.153618623974637 || || compile-allocs/Match || 21000088 || 0.152948131340001 || || compile-allocs/Preds || 20369168 || 0.150245373920468 || || compile-allocs/Preds || 20382840 || 0.14899133906394 || || compile-allocs/BinConv || 21814376 || 0.147565217236013 || || compile-allocs/BinConv || 21843560 || 0.146507544982022 || || compile-allocs/Shapes || 20121512 || 0.144706659929922 || -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 6 10:08:49 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 06 Jul 2016 10:08:49 -0000 Subject: [GHC] #12357: Increasing maximum constraint tuple size significantly blows up compiler allocations In-Reply-To: <046.dd0f12e974ac3c5c9febd70397bf4138@haskell.org> References: <046.dd0f12e974ac3c5c9febd70397bf4138@haskell.org> Message-ID: <061.5ed333f62432ee1b818b3bb0bd22866e@haskell.org> #12357: Increasing maximum constraint tuple size significantly blows up compiler allocations -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.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): Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): For the record, here are the major allocations changes from dd3080fe0263082f65bf2570f49189c277b12e28, ||= Test name =||= Absolute change =||= relative change =|| || compile-allocs/PTTrees || 25393064 || 0.529524950607268 || || compile-allocs/Env || 25411992 || 0.459749707346387 || || compile-allocs/Diff || 25396112 || 0.454698441513462 || || compile-allocs/Attributes || 25401672 || 0.443838549572384 || || compile-allocs/Rotate || 25444576 || 0.425106327638958 || || compile-allocs/MyList || 25454368 || 0.420214761736029 || || compile-allocs/QSort || 25437696 || 0.410709377421855 || || compile-allocs/Defaults || 18059728 || 0.398995946705711 || || compile-allocs/Result || 18067832 || 0.376234141920803 || || compile-allocs/Queue || 25430872 || 0.327207720756636 || || compile-allocs/Type_defs || 25385544 || 0.31841141932715 || || compile-allocs/Getops || 25411824 || 0.305931952326486 || || compile-allocs/Vtslib || 25406880 || 0.297904017772972 || || compile-allocs/Digraph || 25447904 || 0.290609017757 || || compile-allocs/MyRandom || 18052240 || 0.280234183992874 || || compile-allocs/BinTest || 18069304 || 0.266927204744095 || || compile-allocs/RoulSplit || 18036648 || 0.266884025212266 || || compile-allocs/Prog || 18153488 || 0.26291850611499 || || compile-allocs/Match || 25406472 || 0.255481066153786 || || compile-allocs/GamtebMain || 18060416 || 0.254664741449328 || || compile-allocs/PhotoElec || 18076904 || 0.253060115990819 || || compile-allocs/Params || 25428424 || 0.251588917607883 || || compile-allocs/Norm || 18077768 || 0.245577563784965 || || compile-allocs/Checker || 18028920 || 0.229655342982204 || || compile-allocs/FiniteMap || 25446328 || 0.229357595736048 || || compile-allocs/Interact || 18121304 || 0.229086930261854 || || compile-allocs/Dcore || 25456736 || 0.225956351068074 || || compile-allocs/Vector || 18077632 || 0.221214660856509 || || compile-allocs/Elefac || 18106240 || 0.220899224830413 || || compile-allocs/Postscript || 18088816 || 0.215961664665538 || || compile-allocs/Basics || 18147128 || 0.213886880509137 || || compile-allocs/Engine || 18064544 || 0.213754629948678 || || compile-allocs/Pair || 18059280 || 0.212807877872538 || || compile-allocs/Subst || 25469712 || 0.212141133436499 || || compile-allocs/Stdlib || 25446584 || 0.211934106612719 || || compile-allocs/CharSeq || 18020744 || 0.207692636071785 || || compile-allocs/Assemble_loadvec || 18087200 || 0.204241417348172 || || compile-allocs/Tol_cal || 18176248 || 0.201883838406277 || || compile-allocs/Parsers || 25476944 || 0.199030526945435 || -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 6 10:13:38 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 06 Jul 2016 10:13:38 -0000 Subject: [GHC] #12222: ghc panic kindFunResult with template haskell 'isInstance' In-Reply-To: <044.e4acda1a8543a11fc264fd45bad87f99@haskell.org> References: <044.e4acda1a8543a11fc264fd45bad87f99@haskell.org> Message-ID: <059.feed6f97da61c3b6e52603367692e377@haskell.org> #12222: ghc panic kindFunResult with template haskell 'isInstance' -------------------------------------+------------------------------------- Reporter: ghorn | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Template Haskell | Version: 7.10.3 Resolution: duplicate | Keywords: kindFunResult Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: #11694 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by thomie): * status: new => closed * resolution: => duplicate * related: => #11694 Comment: This bug is fixed in 8.0. To make your code work with 8.0, you will have to make the following change to `TH.hs` (see also [wiki:Migration/8.0]): {{{ - go (TyConI (DataD [] _ _ [(NormalC _ [(_,typ)])] _)) = do + go (TyConI (DataD [] _ _ _ [(NormalC _ [(_,typ)])] _)) = do }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 6 10:17:32 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 06 Jul 2016 10:17:32 -0000 Subject: [GHC] #12228: Make newtype polykinded In-Reply-To: <045.481f5e3222a912e93b41f2223714d4b6@haskell.org> References: <045.481f5e3222a912e93b41f2223714d4b6@haskell.org> Message-ID: <060.a20147f24fa390ec25ae632977a1e812@haskell.org> #12228: Make newtype polykinded -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: Type: feature request | Status: closed Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.1 checker) | Resolution: duplicate | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #1311 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by thomie): * status: new => closed * resolution: => duplicate * related: => #1311 Comment: There is recent discussion in #1311, so I'll close this one. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 6 11:59:11 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 06 Jul 2016 11:59:11 -0000 Subject: [GHC] #12368: Demand Analyzer: Cunnig plan not adhered to with aborting fixpoint interation Message-ID: <046.2b784c018fc4a62b657688676ee901f3@haskell.org> #12368: Demand Analyzer: Cunnig plan not adhered to with aborting fixpoint interation -------------------------------------+------------------------------------- Reporter: nomeata | Owner: Type: bug | Status: new Priority: low | 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: -------------------------------------+------------------------------------- Not sure how relevant this is, but when reading both paper and code long enough, on inevitably finds some code smell. This is about nested recursion, as in this example {{{ f [] = [] f (x:xs) = let g [] = f xs g (y:ys) = y+1 : g ys in g (h x) }}} The “cunning plan” of fixpoint iteration (see Note [Initialising strictness]) says that in the first time an inner recursive definition is looked at, its strictness is assumed to be `b` (`botSig`), and from then on, its `idInformation` (presumably from the previous iteration or the outer recursive definition) is used. A flag (`virgin`) in the analysis environment is used to detect that. The problem is that the fixpoint iteration code in `dmdFix` aborts after more than 10 iterations: {{{ loop' n env pairs | found_fixpoint = (env', lazy_fv, pairs') | n >= 10 = (env, lazy_fv, orig_pairs) -- Safe output }}} This means that if the iteration does not terminate, we will “not” attach a strictness signature to the inner binders (`g` in the example above), but rather leave the binders untouched. Then, in the second iteration of finding a fixpoint for `f`, the `virgin` flag is `False`, and `idStrictness` is used, which in this case will simply be the default, namely `nopSig`. I could not produce an example where it matters. And it might be that it simply does not matter, so I’m not sure what to do with this information. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 6 12:02:38 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 06 Jul 2016 12:02:38 -0000 Subject: [GHC] #12369: data families shouldn't be required to have return kind *, data instances should Message-ID: <045.88f660f600999139443e7ddd5881a759@haskell.org> #12369: data families shouldn't be required to have return kind *, data instances should -------------------------------------+------------------------------------- Reporter: ekmett | Owner: Type: feature | Status: new request | Priority: normal | Milestone: 8.2.1 Component: Compiler | Version: 8.0.1 (Type checker) | 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'd like to be able to define {{{#!hs {-# language PolyKinds, KindSignatures, GADTs, TypeFamilies #-} data family Fix :: (k -> *) -> k newtype instance Fix f = In { out :: f (Fix f) } }}} But currently this is disallowed: {{{ Fix.hs:2:1: error: • Kind signature on data type declaration has non-* return kind (k -> *) -> k • In the data family declaration for ‘Fix’ }}} Ultimately I think the issue here is that data __instances__ should be required to end in kind *, not the families, but this generalization didn't mean anything until we had `PolyKinds`. As an example of a usecase, with the above, I could define a bifunctor fixed point such as {{{#!hs newtype instance Fix f a = In2 { out2 :: f (Fix f a) a } }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 6 12:06:16 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 06 Jul 2016 12:06:16 -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.5926c414169d7e8cec922644103ba74c@haskell.org> #12237: Constraint resolution vs. type family resolution vs. TypeErrors -------------------------------------+------------------------------------- Reporter: cactus | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | 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 thomie): * cc: diatchki (added) * related: => #11990 Comment: This seems fixed in GHC HEAD (c88f31a08943764217b69adb1085ba423c9bcf91, 8.1.20160610), perhaps as a result of #11990. {{{ Test.hs:23:16: error: • Unsupported type: Int • In the second argument of ‘($)’, namely ‘foo (Proxy :: Proxy (Int, ()))’ In the expression: print $ foo (Proxy :: Proxy (Int, ())) In an equation for ‘main’: main = print $ foo (Proxy :: Proxy (Int, ())) }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 6 12:28:10 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 06 Jul 2016 12:28:10 -0000 Subject: [GHC] #12240: Common Sense for Type Classes In-Reply-To: <050.3dcf7ad3ce6a480cdc5fe8435e755275@haskell.org> References: <050.3dcf7ad3ce6a480cdc5fe8435e755275@haskell.org> Message-ID: <065.54bd40d999e24cee4a8155e4e8f667ef@haskell.org> #12240: Common Sense for Type Classes -------------------------------------+------------------------------------- Reporter: Mathnerd314 | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 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): Replying to [comment:9 Mathnerd314]: > "The Phabricator upstream is Phacility, Inc. We maintain total control over the project and roadmap. There is no democratic process, voting, or community-driven decision making. This model is better at some things and worse at others than a more community-focused model would be, but it is the model we operate under." > > I am not sure this describes GHC well; wiki:TeamGHC states "GHC's development as a whole is not led by any particular group, company, or individual." Point well taken. I guess I was specifically referring to this passage from that page: Unjustifiable Costs: We support code in the upstream forever. Support is enormously expensive and takes up a huge amount of our time. The cost to support a change over its lifetime is often 10x or 100x or 1000x greater than the cost to write the first version of it. Many uncoordinated patches we receive are "white elephants", which would cost much more to maintain than the value they provide. As an author, it may look like you're giving us free work and we're rejecting it as too expensive, but this viewpoint doesn't align with the reality of a large project which is actively supported by a small, experienced team. Writing code is cheap; maintaining it is expensive. In an ideal world, the GHC maintenance would be democratized. But that's not quite how it currently is (there's a fairly small group that do the regular maintenance) and so we have to guard the door carefully. Part of the reason that insiders' ideas are seen more favorably is that, once you've demonstrated the time and energy to be a regular contributor, it seems more likely that you will maintain the patch -- at least for a while. This lowers the cost of accepting the patch. Shifting direction a bit, we really do need a more open, inclusive process by which ideas (even ones without proper specifications, yet) can be debated by the community, so that it's clearer what the community reaction is. You're going to get a very self-selected slice of the community by debating here. It sounds (from Simon's blog post linked earlier) that there is such a process in the works, and I'm looking forward to learning more about it. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 6 12:29:21 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 06 Jul 2016 12:29:21 -0000 Subject: [GHC] #12369: data families shouldn't be required to have return kind *, data instances should In-Reply-To: <045.88f660f600999139443e7ddd5881a759@haskell.org> References: <045.88f660f600999139443e7ddd5881a759@haskell.org> Message-ID: <060.3b41d2efba969efa895614b19913c7b1@haskell.org> #12369: data families shouldn't be required to have return kind *, data instances should -------------------------------------+------------------------------------- Reporter: ekmett | Owner: Type: feature request | Status: new 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: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): Interesting idea. I can't see a technical problem with it, so maybe we could just allow it. If someone would like to have a go, I'd be a willing reviewer. Alternatively, if it becomes Important to a bunch of people, I could have a go myself. Simon -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 6 12:33:50 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 06 Jul 2016 12:33:50 -0000 Subject: [GHC] #12368: Demand Analyzer: Cunnig plan not adhered to with aborting fixpoint interation In-Reply-To: <046.2b784c018fc4a62b657688676ee901f3@haskell.org> References: <046.2b784c018fc4a62b657688676ee901f3@haskell.org> Message-ID: <061.f7c5afe4bc23a6ae2e187690dd6af07a@haskell.org> #12368: Demand Analyzer: Cunnig plan not adhered to with aborting fixpoint interation -------------------------------------+------------------------------------- Reporter: nomeata | Owner: Type: bug | 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: | -------------------------------------+------------------------------------- Comment (by simonpj): That's quite right. After thinking it briefly (ie I might well be wrong) I don't see a good way to fix it. The trouble is that the fixpoint iteration starts from an unsound assumption: that the function is hyperstrict. It then iterates to a sound conclusion. So if you have to abandon the process, the current approximation is unsound. So you can't just attach it. I don't see how to take advantage of the work done so far. Mind you, 10 iterations is a lot! I think it prints a warning: worth investigating. If it's rare enough it probably doesn't matter much. Simon -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 6 12:41:52 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 06 Jul 2016 12:41:52 -0000 Subject: [GHC] #12368: Demand Analyzer: Cunnig plan not adhered to with aborting fixpoint interation In-Reply-To: <046.2b784c018fc4a62b657688676ee901f3@haskell.org> References: <046.2b784c018fc4a62b657688676ee901f3@haskell.org> Message-ID: <061.7729ba7c8a677bc2750265e6b9c1c03b@haskell.org> #12368: Demand Analyzer: Cunnig plan not adhered to with aborting fixpoint interation -------------------------------------+------------------------------------- Reporter: nomeata | Owner: Type: bug | 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: | -------------------------------------+------------------------------------- Comment (by nomeata): The warning is disabled at the moment. It would be much less rare if we had nested demands on sum types; right now the easiest way to trigger it is a recursive function over a recursive product type (e.g. `data Stream a = S a (Stream a)` or `data BinTree a = Node (BinTree a) a (BinTree a)`. Maybe there is a way to fix this by doing a final single iteration with sound, but conservative assumptions about the strictness signature, and then using `pairs'` instead of `orig_pairs`. This would also make me less worry that the `lazy_fv` returned in the `n>=10` case could be wrong (as they are produced from the unsound assumption). -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 6 13:38:38 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 06 Jul 2016 13:38:38 -0000 Subject: [GHC] #11832: Allow reify to yield types in the current declaration group In-Reply-To: <056.c55a5c5fc06f6b4965766fc5bf61b445@haskell.org> References: <056.c55a5c5fc06f6b4965766fc5bf61b445@haskell.org> Message-ID: <071.6aeab0c8752e3729f7c5efa09db045d2@haskell.org> #11832: Allow reify to yield types in the current declaration group -------------------------------------+------------------------------------- Reporter: | Owner: facundo.dominguez | facundo.dominguez Type: feature request | Status: closed Priority: normal | Milestone: Component: Template Haskell | Version: 7.10.3 Resolution: fixed | Keywords: reify Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2286 Wiki Page: | TemplateHaskell/Reify | -------------------------------------+------------------------------------- Comment (by goldfire): Could you add a Release Note about this, as well? See `docs/users_guide/8.2.1-notes.rst`. Thanks! -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 6 13:54:53 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 06 Jul 2016 13:54:53 -0000 Subject: [GHC] #12370: Implement LetUp in DmdAnal (or document why we do not do it) Message-ID: <046.4d0b4649e15ed41a4a32187881ac4332@haskell.org> #12370: Implement LetUp in DmdAnal (or document why we do not do it) -------------------------------------+------------------------------------- Reporter: nomeata | Owner: Type: task | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.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 paper “Modular, Higher-Order Cardinality Analysis in Theory and Practice” has two rules for analizing let-bindings: LetDown, used for functions, that determines the function’s strictness signature, and passes it down, and LetUp, used for thunks, which uses the demand coming from the scope. The implementation uses only LetDown for all let-bindings. I wonder why this is so. I implemented something that looks like LetUp and will validate and performance-test it soon, in order to either make the implementation match the analysis, or alternatively document why this is the case. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 6 14:13:30 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 06 Jul 2016 14:13:30 -0000 Subject: [GHC] #12370: Implement LetUp in DmdAnal (or document why we do not do it) In-Reply-To: <046.4d0b4649e15ed41a4a32187881ac4332@haskell.org> References: <046.4d0b4649e15ed41a4a32187881ac4332@haskell.org> Message-ID: <061.697fede8257e63f6de189f70a7484d07@haskell.org> #12370: Implement LetUp in DmdAnal (or document why we do not do it) -------------------------------------+------------------------------------- Reporter: nomeata | Owner: Type: task | Status: new Priority: normal | Milestone: Component: Compiler | 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 nomeata): Work in progress in branch `wip/T12370`. It already works in this simple case: {{{ foo :: (Int, Int) -> Int foo (x,y) = x + y {-# NOINLINE foo #-} bar n m = let p = (n,m) {-# NOINLINE p #-} in foo p }}} Here, bar now gets the very detailed signature `m` instead of just `m`. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 6 16:34:01 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 06 Jul 2016 16:34:01 -0000 Subject: [GHC] #5728: Warnings from -fwarn-incomplete-record-updates even with all constructors matched In-Reply-To: <042.3d8c83f19998d498d52985dfe7e74f1d@haskell.org> References: <042.3d8c83f19998d498d52985dfe7e74f1d@haskell.org> Message-ID: <057.8517653d77d5bb5b4b6a7bfc753c0125@haskell.org> #5728: Warnings from -fwarn-incomplete-record-updates even with all constructors matched -------------------------------------+------------------------------------- Reporter: mjo | Owner: Type: bug | Status: closed Priority: normal | Milestone: ⊥ Component: Compiler | Version: 7.4.1 Resolution: duplicate | Keywords: warnings 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 mjo): For what it's worth, this is still present in 8.0.1. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 6 17:13:42 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 06 Jul 2016 17:13:42 -0000 Subject: [GHC] #12364: Demand analysis for sum types In-Reply-To: <046.d2210fe5d78e7148b495c8c2b1cf9322@haskell.org> References: <046.d2210fe5d78e7148b495c8c2b1cf9322@haskell.org> Message-ID: <061.e0f5e76fc43d9cd8da586aa22cae4b5f@haskell.org> #12364: Demand analysis for sum types -------------------------------------+------------------------------------- Reporter: nomeata | Owner: Type: task | 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 jmct): Hey everyone, I hope it's okay if I chime in for a second. I was also originally writting this comment on #12368 but I think it's a bit more relevant here. Because of what Simon says on ticket:12368#comment:1, fixpoint convergence should not be used to perform strictness analysis on recursive sum types. I could probably dig up some examples of where it produces incorrect results if you'd like. The standard way of handling recursive types is to ensure they're regular types, which allows you to assume a 'uniform' demand on the type. The frustrating thing when trying to apply this to Haskell is polymorphic recursion which would allow for non-uniform demands on a recursive type. For the unboxing of sum-types we wanted to get around this by checking whether we were analysing a recursive sum type, but that turns out to be difficult in GHC at the moment: https://mail.haskell.org/pipermail/ghc- devs/2016-March/011526.html However, that only works for us because we only want to unbox non- recursive things anyway. If you definitely want to analyse recursive types then some new theory is going to have to be worked out. The unexplored parts are strictness on nested types and the higher-kinded polymorphism possibly allowing for introduction of loops. I've thought a bit about how to do it but haven't had a serious go at it. During my thesis defense Prof. Mycoft suggested the problem might be solvable using a PER-based analysis, which has been shown to generalize projection-based analyses. I haven't looked at that approach yet, but I did scribble down a particular thesis he told me to read. For some background, Hinze's thesis is (IMO) the best this topic. I've read and re-read his thesis several times in the past few years and I still get new insight from it each time. You can find it on his site here: http://www.cs.ox.ac.uk/ralf.hinze/publications/#D2 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 6 21:16:00 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 06 Jul 2016 21:16:00 -0000 Subject: [GHC] #12370: Implement LetUp in DmdAnal (or document why we do not do it) In-Reply-To: <046.4d0b4649e15ed41a4a32187881ac4332@haskell.org> References: <046.4d0b4649e15ed41a4a32187881ac4332@haskell.org> Message-ID: <061.f52ec8cb97c5f24ecbca00efdadcf5d3@haskell.org> #12370: Implement LetUp in DmdAnal (or document why we do not do it) -------------------------------------+------------------------------------- Reporter: nomeata | Owner: Type: task | Status: new Priority: normal | Milestone: Component: Compiler | 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 nomeata): I have an implementation now, and I think it does what it should. Performance measurements, though, indicate no significant changes whatsoever: https://perf.haskell.org/ghc/#revision/04ded5e3c0bcc359f4b46958b5942b8230af1b28 The programs get consistently smaller by 0.02%. The test suite goes through with the exception of a single test: {{{ Actual stderr output differs from expected: --- ./simplCore/should_compile/spec-inline.run/spec- inline.stderr.normalised 2016-07-06 18:06:21.855289459 +0200 +++ ./simplCore/should_compile/spec-inline.run/spec- inline.comp.stderr.normalised 2016-07-06 18:06:21.855289459 +0200 @@ -43,7 +43,7 @@ -- RHS size: {terms: 55, types: 9, coercions: 0} Roman.foo_$s$wgo [Occ=LoopBreaker] :: GHC.Prim.Int# -> GHC.Prim.Int# -> GHC.Prim.Int# -[GblId, Arity=2, Caf=NoCafRefs, Str=] +[GblId, Arity=2, Caf=NoCafRefs, Str=] Roman.foo_$s$wgo = / (sc :: GHC.Prim.Int#) (sc1 :: GHC.Prim.Int#) -> let { *** unexpected failure for spec-inline(optasm) }}} And this “better” signature does not matter, as the argument is unlifted anyways. I will separately measure if this increases the number of thunks determined to be one-shot. But even if it did, it does not matter much, as shown by nofib. The code change (changeset:04ded5e3c0bcc359f4b46958b5942b8230af1b28/ghc) is relatively small and brings it closer to the paper. Is it worth getting that in shape for master, or should we not bother? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 6 21:17:13 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 06 Jul 2016 21:17:13 -0000 Subject: [GHC] #12364: Demand analysis for sum types In-Reply-To: <046.d2210fe5d78e7148b495c8c2b1cf9322@haskell.org> References: <046.d2210fe5d78e7148b495c8c2b1cf9322@haskell.org> Message-ID: <061.8598c930325b88c980ea6025d66ff491@haskell.org> #12364: Demand analysis for sum types -------------------------------------+------------------------------------- Reporter: nomeata | Owner: Type: task | 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 nomeata): > I could probably dig up some examples of where it produces incorrect results if you'd like. Isn’t it like that similar example will work for recursive product types, and hence be (likely obscure and rare, but still real) bugs in the current code? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 6 22:32:28 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 06 Jul 2016 22:32:28 -0000 Subject: [GHC] #12364: Demand analysis for sum types In-Reply-To: <046.d2210fe5d78e7148b495c8c2b1cf9322@haskell.org> References: <046.d2210fe5d78e7148b495c8c2b1cf9322@haskell.org> Message-ID: <061.5f5ba3b4c54d19110fd1889f450176fb@haskell.org> #12364: Demand analysis for sum types -------------------------------------+------------------------------------- Reporter: nomeata | Owner: Type: task | 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 jmct): Possibly, but GHC's much better about detecting recursiveness for product types, see the large section titled "Deciding which type constructors are recursive" in compiler/typecheck/TcTyDecls.hs. In particular there's this section: {{{ The "recursive" flag for algebraic data types is irrelevant (never consulted) for types with more than one constructor. An algebraic data type M.T is "recursive" iff it has just one constructor, and (a) it is declared in an hi-boot file (see RdrHsSyn.hsIfaceDecl) (b) it is declared in a source file, but that source file has a companion hi-boot file which declares the type or (c) one can get from its arg types to T via type synonyms, or by non-recursive newtypes or non-recursive product types in M e.g. data T = MkT (T -> Int) Bool }}} I'm going to speculate wildly and say that it just hasn't been that important for GHC to detect recursiveness in sum types in the past, and therefore it just hasn't gotten very much attention. There probably shouldn't be a difference in theory, but GHC as it is today is better at avoiding recursiveness in product types and therefore would be better at avoiding the issue in that case. Though you're right in principle. Tomorrow morning I'll dig up my old notes and comment on #12368 giving an example. I don't want to confuse the two issues too much, though they're intimately related. #12368 is really about recursion in the _functions_ though, which is an important distinction (and I definitely have examples where the current behavior of the 'cunning plan' is necessary). -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 7 00:12:44 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 07 Jul 2016 00:12:44 -0000 Subject: [GHC] #12371: Error message, room for improvement Message-ID: <051.4451bd27ef0d80311d9b31d3cc46b800@haskell.org> #12371: Error message, room for improvement -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Keywords: | Operating System: Unknown/Multiple TypeApplications | Architecture: | Type of failure: Incorrect Unknown/Multiple | warning at compile-time Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- {{{ $ ghci -ignore-dot-ghci GHCi, version 8.0.1: http://www.haskell.org/ghc/ :? for help Prelude> :set -XPatternSynonyms Prelude> :set -XViewPatterns Prelude> pattern Foo a <- ((\uncons -> Just (a, as) -> a) -> a) :3:20: error: Pattern syntax in expression context: \ uncons -> Just (a, as) -> a Did you mean to enable TypeApplications? }}} Let's: {{{ Prelude> :set -XTypeApplications Prelude> pattern Foo a <- ((\uncons -> Just (a, as) -> a) -> a) :5:20: error: Pattern syntax in expression context: \ uncons -> Just (a, as) -> a Did you mean to enable TypeApplications? Prelude> }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 7 02:16:35 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 07 Jul 2016 02:16:35 -0000 Subject: [GHC] #12372: bug: documentation for Control.Monad.guard not useful after AMP Message-ID: <043.bd49d884aa9da8caf539111086601a3f@haskell.org> #12372: bug: documentation for Control.Monad.guard not useful after AMP -------------------------------------+------------------------------------- Reporter: ntc2 | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: | Version: 8.0.1 libraries/base | 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: -------------------------------------+------------------------------------- Since the AMP refactor, the documentation for `Control.Monad.guard` [1] is no longer useful for beginners. It simply gives the definition of `guard`, but in prose: {{{ guard b is pure () if b is True, and empty if b is False. }}} (and better to just use Haskell instead of prose here, no?) To use `guard` in a `MonadPlus`, you now need to know that `Alternative` is a super class of `MonadPlus`, and that `mzero = zero`. The documentation [2] for `MonadPlus` doens't mention `mzero = zero` in the default definition -- you must look at the source for that -- and the docs for `guard` don't mention `MonadPlus`. The documentation for `Control.Monad.guard` should suggest use with `MonadPlus`, and give an example (compare with the very helpful example for `Control.Monad.when`). A non-monadic example would also be useful. [1] https://hackage.haskell.org/package/base-4.9.0.0/docs/Control- Monad.html#v:guard [2] https://hackage.haskell.org/package/base-4.9.0.0/docs/Control- Monad.html#t:MonadPlus -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 7 04:07:46 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 07 Jul 2016 04:07:46 -0000 Subject: =?utf-8?q?Re=3A_=5BGHC=5D_=2311632=3A_Data=2EChar_repeated_readL?= =?utf-8?q?itChar_barfs_on_output_from_show_=22=C3=B31=22?= In-Reply-To: <049.9bf2436e7fb9c211d83d1b0ba3c6ee23@haskell.org> References: <049.9bf2436e7fb9c211d83d1b0ba3c6ee23@haskell.org> Message-ID: <064.e76edc61892500383c81eb0ac1c79fac@haskell.org> #11632: Data.Char repeated readLitChar barfs on output from show "ó1" -------------------------------------+------------------------------------- Reporter: inversemot | Owner: kgupta Type: bug | Status: new Priority: normal | Milestone: Component: libraries/base | Version: 7.10.3 Resolution: | Keywords: newcomer Operating System: Linux | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: readLitChar Blocked By: | Blocking: Related Tickets: | Differential Rev(s): D2391 Wiki Page: | -------------------------------------+------------------------------------- Changes (by kgupta): * testcase: => readLitChar * differential: => D2391 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 7 08:01:29 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 07 Jul 2016 08:01:29 -0000 Subject: [GHC] #11617: DYLD_LIBRARY_PATH ignored on Mac OS X 10.11.x In-Reply-To: <047.d00a5696b889c6d842cf8ac7cce9d67a@haskell.org> References: <047.d00a5696b889c6d842cf8ac7cce9d67a@haskell.org> Message-ID: <062.4c3622832007e258f9bad112975bf26e@haskell.org> #11617: DYLD_LIBRARY_PATH ignored on Mac OS X 10.11.x ---------------------------------+-------------------------------------- Reporter: borsboom | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: hsc2hs | Version: 7.10.3 Resolution: | Keywords: Operating System: MacOS X | Architecture: x86_64 (amd64) Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #8266, #8721 | Differential Rev(s): Wiki Page: | ---------------------------------+-------------------------------------- Comment (by darchon): TL;DR @thomie: After some consideration, I agree with the "wontfix". I know of one "valid" reason to set the (DY)LD_LIBRARY_PATH environment variable in a "standard" Haskell development environment, and that is when there are dynamically-linked executables in a testing situation (i.e. a dynamically linked executable created by {{{cabal test}}}). This is based on what I said here: https://github.com/haskell/cabal/issues/2330#issuecomment-69201669 As of Cabal-1.22, Cabal sets all the RPATHs instead of letting GHC handle them. What Cabal does differently from GHC, is that it sets the RPATHs to the final install locations, not the directory where the library currently resides. Now, for installed libraries, the final install location and the directory where the library currently resides are one and the same; however, for a library under development, the final install location is very must likely different from the place it currently resides: {{{./dist/build}}}. So, since a dynamically-linked executable created by {{{cabal test}}} is created the same way as any other dynamically-linked executable, I had to find a way for the created test executable to find the library under development. The way I did this is have {{{cabal test}}} run the test executable in an environment where (DY)LD_LIBRARY_PATH includes {{{.dist/build}}}: https://github.com/haskell/cabal/blob/6357bc536f993542fc385e3d1a59dac5f8b61268/Cabal/Distribution/Simple/Test/LibV09.hs#L85 However, since I don't see how the dynamically linked testing executables can end up in one of the protected system locations, their (DY)LD_LIBRARY_PATH environment variables will not be stripped. Consequently, this one "valid" use of (DY)LD_LIBRARY_PATH is not affected by OS X's behaviour. So for now, I agree with the "wontfix", unless someone can truly point out another valid reason to set (DY)LD_LIBRARY_PATH. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 7 08:07:24 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 07 Jul 2016 08:07:24 -0000 Subject: [GHC] #12364: Demand analysis for sum types In-Reply-To: <046.d2210fe5d78e7148b495c8c2b1cf9322@haskell.org> References: <046.d2210fe5d78e7148b495c8c2b1cf9322@haskell.org> Message-ID: <061.15b999760aae6e1f054fbd766226bb63@haskell.org> #12364: Demand analysis for sum types -------------------------------------+------------------------------------- Reporter: nomeata | Owner: Type: task | 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 nomeata): I was about to say “But this flag is not checked anywhere in the demand analyzer” (because it is) and did some git archeology, and I found commit changeset:3e7e5ba8333d318c38b4cfc538a97fdca0aed5b1/ghc which replaced the use of `isRecursiveTyCon` with one using `RecTcChecker`. From my rough reading is that we look one level deep ''on every iteration'', so we still get deeply nested result. I was able to produce an unsound result this way, but it belongs to #12368, so I added it there as a comment. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 7 08:08:07 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 07 Jul 2016 08:08:07 -0000 Subject: [GHC] #12368: Demand Analyzer: Cunnig plan not adhered to with aborting fixpoint interation In-Reply-To: <046.2b784c018fc4a62b657688676ee901f3@haskell.org> References: <046.2b784c018fc4a62b657688676ee901f3@haskell.org> Message-ID: <061.3b2214e0fb0a7523607398ce039f9ef2@haskell.org> #12368: Demand Analyzer: Cunnig plan not adhered to with aborting fixpoint interation -------------------------------------+------------------------------------- Reporter: nomeata | Owner: Type: bug | 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: | -------------------------------------+------------------------------------- Comment (by nomeata): I could trigger an unsound result this way: {{{#!hs module DmdFixBug where -- Needs to be a product type data Stream = S Int Stream bar s = foo s where foo :: Stream -> Int foo (S n s) = n + foo s }}} that terminate only because of the 10-iteration-limit, and as you can see, the result is wrong (there is an “absent” value that is not absent) {{{ bar :: Stream -> Int [LclIdX, Arity=1, Str=b, Unf=Unf{Src=InlineStable, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=ALWAYS_IF(arity=1,unsat_ok=True,boring_ok=True) Tmpl= \ (s_axX [Occ=Once] :: Stream) -> foo_sK7 s_axX}] bar = \ (s_axX [Dmd=] :: Stream) -> foo_sK7 s_axX }}} (I need to wrap `foo` in `bar` because `foo` does not get a strictness result attached, because the analysis fails.) I’ll see if I can actually make the program crash, and turn this into a proper test suite test case. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 7 08:17:55 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 07 Jul 2016 08:17:55 -0000 Subject: [GHC] #12370: Implement LetUp in DmdAnal (or document why we do not do it) In-Reply-To: <046.4d0b4649e15ed41a4a32187881ac4332@haskell.org> References: <046.4d0b4649e15ed41a4a32187881ac4332@haskell.org> Message-ID: <061.1fa4ffc9bffeff23c1da10d133458533@haskell.org> #12370: Implement LetUp in DmdAnal (or document why we do not do it) -------------------------------------+------------------------------------- Reporter: nomeata | Owner: Type: task | Status: new Priority: normal | Milestone: Component: Compiler | 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 simonpj): That changeset isn't in the repo. Perhaps you meant [https://git.haskell.org/ghc.git/commitdiff/aa472d7bf13bbeb390e857c95c8b92d90d6246ae this one]? Yes, that looks like a good change to me; simple and worth doing. Make `isLam` look through casts perhaps. I'd had hoped that we could eliminate the `is_thunk` stuff in `dmdAnalRhs`, which would make the change a bigger win. But for recursive RHSs we might still see a non-lambda in `dmdAnalRhs`. But I'm hazy about the `trimCPR` and `splitFVs` stuff (which is ill-documented) so it may be that for the recursive case we can just do something simpler and more conservative. If we have mutual recursion with a non-lambda, I doubt we are going to get much useful. There must be simple examples where there really is a win; maybe add one as a regression test so we will see if we lose it? For the triv-rhs part, there's a bit of fancy footwork in `dmdAnalRhs` that you don't seem to be doing here... why? Another infelicity in the existing setup. What about `foo = g x` where `g` has arity 2? This RHS is a partial application and morally we should get the same as `foo = \y. g x y`. But I doubt we do. Fixing this might be a small win too. GHC's policy right now is NOT to eta-expand partial applications (I forget why; we could consider revisiting that decision). -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 7 08:21:54 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 07 Jul 2016 08:21:54 -0000 Subject: [GHC] #12370: Implement LetUp in DmdAnal (or document why we do not do it) In-Reply-To: <046.4d0b4649e15ed41a4a32187881ac4332@haskell.org> References: <046.4d0b4649e15ed41a4a32187881ac4332@haskell.org> Message-ID: <061.38455ec1164f4d46a5f3a7f6426a4bc1@haskell.org> #12370: Implement LetUp in DmdAnal (or document why we do not do it) -------------------------------------+------------------------------------- Reporter: nomeata | Owner: Type: task | Status: new Priority: normal | Milestone: Component: Compiler | 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 nomeata): > That changeset isn't in the repo. Perhaps you meant ​this one? Yes; there is no good stable way to refer to changesets on rebasing branches, unfortunately. > Make isLam look through casts perhaps. As the comment indicates, it mirros the behavior of `collectBinders e`, because if `collectBinders` does not find any binders, then LetDown is not going to perform well. I will expand the comment to explain this reasoning. > There must be simple examples where there really is a win; maybe add one as a regression test so we will see if we lose it? I will produce an example where we can see a difference in the analysis result. > For the triv-rhs part, there's a bit of fancy footwork in dmdAnalRhs that you don't seem to be doing here... why? I simply don’t handle the case and let it fall through to `dmdAnalRhs`. Will add a note, or refactor. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 7 08:28:33 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 07 Jul 2016 08:28:33 -0000 Subject: [GHC] #8721: Testsuite not reporting errors for DYN way on OS X In-Reply-To: <046.8af9e017e06f897fefadc3e624641754@haskell.org> References: <046.8af9e017e06f897fefadc3e624641754@haskell.org> Message-ID: <061.10f0951fbd80aa86980fd81c840fc605@haskell.org> #8721: Testsuite not reporting errors for DYN way on OS X -------------------------------+---------------------------------------- Reporter: darchon | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Test Suite | Version: 7.6.3 Resolution: | Keywords: dynamic linking Operating System: MacOS X | Architecture: Unknown/Multiple Type of failure: Other | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------+---------------------------------------- Changes (by thomie): * status: closed => new * resolution: fixed => Comment: Replying to [comment:3 darchon]: > No, it does not mean that we can refrain from setting `DYLD_LIBRARY_PATH`. in f7be53ac9dac85b83e7fe5ecede01b98a572ba48, the rpaths are made relative to the final install location. During testing, the libraries are still in their build locations, so we still need `DYLD_LIBRARY_PATH` to find the libraries. We can do better. A normal `validate` //installs// the in-tree GHC into a directory `bindisttest/`, and then starts a testsuite run with `BINDIST=YES`. The testsuite driver then uses this //installed// GHC. Not setting `DYLD_LIBRARY_PATH` when `BINDIST=YES` should give us better coverage for DYN way on OS X, as this ticket requested. I don't have access to a Mac, but reopening for someone who does. I still wonder why on Linux we don't have to set `LD_LIBRARY_PATH`. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 7 08:38:40 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 07 Jul 2016 08:38:40 -0000 Subject: [GHC] #12368: Demand Analyzer: Cunnig plan not adhered to with aborting fixpoint interation In-Reply-To: <046.2b784c018fc4a62b657688676ee901f3@haskell.org> References: <046.2b784c018fc4a62b657688676ee901f3@haskell.org> Message-ID: <061.d8f90aee73ea86158203d4f3650bfe50@haskell.org> #12368: Demand Analyzer: Cunnig plan not adhered to with aborting fixpoint interation -------------------------------------+------------------------------------- Reporter: nomeata | Owner: Type: bug | 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: | -------------------------------------+------------------------------------- Comment (by Joachim Breitner ): In [changeset:"b9cea81ded5dc4da19fc011d96f28ade660438c2/ghc" b9cea81d/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="b9cea81ded5dc4da19fc011d96f28ade660438c2" Show testcase where demand analysis abortion code fails By making it believe that some deeply nested value is absent when it really isn't. See #12368. }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 7 08:39:59 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 07 Jul 2016 08:39:59 -0000 Subject: [GHC] #12368: Demand Analyzer: Cunnig plan not adhered to with aborting fixpoint interation In-Reply-To: <046.2b784c018fc4a62b657688676ee901f3@haskell.org> References: <046.2b784c018fc4a62b657688676ee901f3@haskell.org> Message-ID: <061.58bc76b5e8914a00fcaf193620dbb5c6@haskell.org> #12368: Demand Analyzer: Cunnig plan not adhered to with aborting fixpoint interation -------------------------------------+------------------------------------- Reporter: nomeata | Owner: Type: bug | 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: | -------------------------------------+------------------------------------- Comment (by nomeata): I could make it trigger a `T12368: Oops! Entered absent arg w Stream`; test case as `T12368`. I think the fix is, if the number of iterations exceeds the limit, to do a final run with most pessimistic assumptions about the strictness signatures of the things in the recursive group. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 7 08:49:18 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 07 Jul 2016 08:49:18 -0000 Subject: [GHC] #11617: DYLD_LIBRARY_PATH ignored on Mac OS X 10.11.x In-Reply-To: <047.d00a5696b889c6d842cf8ac7cce9d67a@haskell.org> References: <047.d00a5696b889c6d842cf8ac7cce9d67a@haskell.org> Message-ID: <062.c1b1c246117eb19478a07aacad9c6724@haskell.org> #11617: DYLD_LIBRARY_PATH ignored on Mac OS X 10.11.x ---------------------------------+-------------------------------------- Reporter: borsboom | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: hsc2hs | Version: 7.10.3 Resolution: wontfix | Keywords: Operating System: MacOS X | Architecture: x86_64 (amd64) Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #8266, #8721 | Differential Rev(s): Wiki Page: | ---------------------------------+-------------------------------------- Changes (by thomie): * status: new => closed * resolution: => wontfix Comment: Great explanation, thanks. Good thing GHC/Cabal doesn't rely on DYLD_LIBRARY_PATH (for installed libraries). We would be in a lot of trouble now if it did. I still don't understand the original problem reported to reddit (https://www.reddit.com/r/haskell/comments/3ooxu4/library_not_loaded_libmariadb2dylib_os_x/, "I cloned the mysql package from bos/mysql and replaced the call to mysql_config program to mariadb_config program."). Maybe there's another bug somewhere, but it is unlikely GHC's fault. Closing this issue as wontfix. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 7 08:57:23 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 07 Jul 2016 08:57:23 -0000 Subject: [GHC] #12370: Implement LetUp in DmdAnal (or document why we do not do it) In-Reply-To: <046.4d0b4649e15ed41a4a32187881ac4332@haskell.org> References: <046.4d0b4649e15ed41a4a32187881ac4332@haskell.org> Message-ID: <061.fba20341c4e39e258d6fc1775979b062@haskell.org> #12370: Implement LetUp in DmdAnal (or document why we do not do it) -------------------------------------+------------------------------------- Reporter: nomeata | Owner: Type: task | Status: new Priority: normal | Milestone: Component: Compiler | 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 nomeata): > I will separately measure if this increases the number of thunks determined to be one-shot. But even if it did, it does not matter much, as shown by nofib. Again, only insignificant changes, not worth mentioning. The number of thunks in total goes up by 0.06%, precision of the analysis is now 24.9% instead of 24.8%. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 7 09:12:43 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 07 Jul 2016 09:12:43 -0000 Subject: [GHC] #12372: bug: documentation for Control.Monad.guard not useful after AMP In-Reply-To: <043.bd49d884aa9da8caf539111086601a3f@haskell.org> References: <043.bd49d884aa9da8caf539111086601a3f@haskell.org> Message-ID: <058.0482989b39c2d1b79d4be2a4d7634fc4@haskell.org> #12372: bug: documentation for Control.Monad.guard not useful after AMP -------------------------------------+------------------------------------- Reporter: ntc2 | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: libraries/base | 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: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * cc: ekmett, core-libraries-committee@… (added) Comment: Thanks. This is a question for the Core Libraries Committee, cc'd -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 7 09:15:01 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 07 Jul 2016 09:15:01 -0000 Subject: [GHC] #12368: Demand Analyzer: Cunnig plan not adhered to with aborting fixpoint interation In-Reply-To: <046.2b784c018fc4a62b657688676ee901f3@haskell.org> References: <046.2b784c018fc4a62b657688676ee901f3@haskell.org> Message-ID: <061.2b3fdc19deefcccda159f3d456cd0801@haskell.org> #12368: Demand Analyzer: Cunnig plan not adhered to with aborting fixpoint interation -------------------------------------+------------------------------------- Reporter: nomeata | Owner: Type: bug | 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: | -------------------------------------+------------------------------------- Comment (by simonpj): Are you saying that the existing abortion mechanism, which returns to `orig_pairs` is unsound too? I didn't know that. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 7 09:22:26 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 07 Jul 2016 09:22:26 -0000 Subject: [GHC] #12368: Demand Analyzer: Cunnig plan not adhered to with aborting fixpoint interation In-Reply-To: <046.2b784c018fc4a62b657688676ee901f3@haskell.org> References: <046.2b784c018fc4a62b657688676ee901f3@haskell.org> Message-ID: <061.44aa0127682baf6f7dbd9d7cb5e54d36@haskell.org> #12368: Demand Analyzer: Cunnig plan not adhered to with aborting fixpoint interation -------------------------------------+------------------------------------- Reporter: nomeata | Owner: Type: bug | 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:D2392 Wiki Page: | -------------------------------------+------------------------------------- Changes (by nomeata): * status: new => patch * differential: => Phab:D2392 Comment: That’s my impression. I propose a fix in https://phabricator.haskell.org/D2392 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 7 09:28:09 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 07 Jul 2016 09:28:09 -0000 Subject: [GHC] #12360: Extend support for binding implicit parameters In-Reply-To: <051.60aab356d30170c681e545a4ae0a0e84@haskell.org> References: <051.60aab356d30170c681e545a4ae0a0e84@haskell.org> Message-ID: <066.0c99f0f48d581a82ad4ca108bb16c9f9@haskell.org> #12360: Extend support for binding implicit parameters -------------------------------------+------------------------------------- Reporter: MichaelBurge | Owner: 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: | -------------------------------------+------------------------------------- Comment (by simonpj): Iceland_jack: I could not parse your comments. But currently GHC does allow this: {{{ data X where MkX :: (?x :: Int) => X f :: X -> Int -> Int f MkX y = ?x + y -- The pattern match on MkX binds an -- implicit parameter ?x g = let ?x = 7 in f MkX 5 -- Here the MkX needs a ?x constraint, which it gets from -- the let-binding. So g = 12 }}} Function `f` looks a bit odd because it has a use of `?x` but it is far from clear where it is bound: you have to look at the captured constraints for the pattern-matched constructors. But there is nothing technically complicated or unsound about this. Pattern synonyms are just sugar on top of this. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 7 09:52:14 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 07 Jul 2016 09:52:14 -0000 Subject: [GHC] #12373: Type error but types match Message-ID: <043.bd1a92d82c4b4533b5d9ddee0a7fc4ab@haskell.org> #12373: Type error but types match -------------------------------------+------------------------------------- Reporter: osa1 | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.1 (Type checker) | 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: -------------------------------------+------------------------------------- {{{ > unboxedsums git:(prim_sums_rebase_5) x cat primop_bug.hs {-# LANGUAGE MagicHash, ScopedTypeVariables, UnboxedTuples #-} module Main where import GHC.MVar import GHC.Prim import GHC.Types main :: IO () main = IO (\rw -> newMVar# rw) >> return () > unboxedsums git:(prim_sums_rebase_5) x ghc-stage1 primop_bug.hs -ddump- stg -ddump-cmm -ddump-to-file -fforce-recomp -dumpdir primop_fails -O -fprint-explicit-kinds [1 of 1] Compiling Main ( primop_bug.hs, primop_bug.o ) primop_bug.hs:10:19: error: • Couldn't match a lifted type with an unlifted type Expected type: (# State# RealWorld, MVar# RealWorld a0 #) Actual type: (# State# RealWorld, MVar# RealWorld a0 #) • In the expression: newMVar# rw In the first argument of ‘IO’, namely ‘(\ rw -> newMVar# rw)’ In the first argument of ‘(>>)’, namely ‘IO (\ rw -> newMVar# rw)’ }}} Tried with HEAD, 8.0.1. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 7 10:45:15 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 07 Jul 2016 10:45:15 -0000 Subject: [GHC] #12372: bug: documentation for Control.Monad.guard not useful after AMP In-Reply-To: <043.bd49d884aa9da8caf539111086601a3f@haskell.org> References: <043.bd49d884aa9da8caf539111086601a3f@haskell.org> Message-ID: <058.26efd87a23526919d316c38074bc39f1@haskell.org> #12372: bug: documentation for Control.Monad.guard not useful after AMP -------------------------------------+------------------------------------- Reporter: ntc2 | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: libraries/base | 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: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by ekmett): Do you have an example of the text you'd prefer? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 7 10:54:03 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 07 Jul 2016 10:54:03 -0000 Subject: [GHC] #4012: Compilation results are not deterministic In-Reply-To: <043.9c3dc141e8901acb12e4d7c1e6038096@haskell.org> References: <043.9c3dc141e8901acb12e4d7c1e6038096@haskell.org> Message-ID: <058.014c53074ec59d8a01e7e555326a8a78@haskell.org> #4012: Compilation results are not deterministic -------------------------------------+------------------------------------- Reporter: kili | Owner: niteria Type: bug | Status: new Priority: high | Milestone: 8.2.1 Component: Compiler | Version: 6.12.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Other | Test Case: Blocked By: 11362 | Blocking: 12262 Related Tickets: #10424 | Differential Rev(s): Phab:D910, | Phab:D1073, Phab:D1133, Phab:D1192, | Phab:D1268, Phab:D1360, Phab:D1373, Wiki Page: | Phab:D1396, Phab:D1457, Phab:D1468, DeterministicBuilds | Phab:D1487, Phab:D1504, Phab:D1508 -------------------------------------+------------------------------------- Comment (by Bartosz Nitka ): In [changeset:"6ed7c4793fe1acd491646a8312afbbda6be1fd0b/ghc" 6ed7c479/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="6ed7c4793fe1acd491646a8312afbbda6be1fd0b" Document some codegen nondeterminism Bit-for-bit reproducible binaries are not a goal for now, so this is just marking places that could be a problem. Doing this will allow eltsUFM to be removed and will leave only nonDetEltsUFM. GHC Trac: #4012 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 7 11:10:41 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 07 Jul 2016 11:10:41 -0000 Subject: [GHC] #12373: Type error but types match In-Reply-To: <043.bd1a92d82c4b4533b5d9ddee0a7fc4ab@haskell.org> References: <043.bd1a92d82c4b4533b5d9ddee0a7fc4ab@haskell.org> Message-ID: <058.8c9e990b0c5c61c07040da38fe64b51c@haskell.org> #12373: Type error but types match -------------------------------------+------------------------------------- Reporter: osa1 | Owner: Type: bug | Status: new Priority: normal | Milestone: 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: | -------------------------------------+------------------------------------- Comment (by simonpj): The error message is dire, but the error is real. {{{ -- Type of data constructor for IO: IO :: forall a. State# RealWorld -> (# State# RealWorld, a #) -- Type of newMVar# newMVar# :: forall b. State# s -> (# State# s, MVar# s b #) }}} So when we apply `IO` to `newMVar#` we have to instantiate the `forall a` with `MVar# s b` which isn't allowed. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 7 12:12:45 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 07 Jul 2016 12:12:45 -0000 Subject: [GHC] #12373: Type error but types match In-Reply-To: <043.bd1a92d82c4b4533b5d9ddee0a7fc4ab@haskell.org> References: <043.bd1a92d82c4b4533b5d9ddee0a7fc4ab@haskell.org> Message-ID: <058.0531d028572adb50c58e5e4ea6d33c92@haskell.org> #12373: Type error but types match -------------------------------------+------------------------------------- Reporter: osa1 | Owner: Type: bug | Status: new Priority: normal | Milestone: 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: | -------------------------------------+------------------------------------- Comment (by goldfire): This is probably #11198. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 7 12:13:15 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 07 Jul 2016 12:13:15 -0000 Subject: [GHC] #11198: TypeInType error message regressions In-Reply-To: <047.10bc7f90bc6ecc2eebe9257004fabdc3@haskell.org> References: <047.10bc7f90bc6ecc2eebe9257004fabdc3@haskell.org> Message-ID: <062.7e825321a2c23bc1a34dd67ddadaa000@haskell.org> #11198: TypeInType error message regressions -------------------------------------+------------------------------------- Reporter: goldfire | Owner: Type: bug | Status: new Priority: high | Milestone: 8.0.2 Component: Compiler (Type | Version: 7.11 checker) | Keywords: TypeInType, Resolution: | ErrorMessages Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #11672 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by goldfire): See also #12373, which looks quite similar to this bug. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 7 12:37:12 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 07 Jul 2016 12:37:12 -0000 Subject: =?utf-8?q?Re=3A_=5BGHC=5D_=2311632=3A_Data=2EChar_repeated_readL?= =?utf-8?q?itChar_barfs_on_output_from_show_=22=C3=B31=22?= In-Reply-To: <049.9bf2436e7fb9c211d83d1b0ba3c6ee23@haskell.org> References: <049.9bf2436e7fb9c211d83d1b0ba3c6ee23@haskell.org> Message-ID: <064.2d97c68f9cb30f211a323999b231ac34@haskell.org> #11632: Data.Char repeated readLitChar barfs on output from show "ó1" -------------------------------------+------------------------------------- Reporter: inversemot | Owner: kgupta Type: bug | Status: patch Priority: normal | Milestone: 8.2.1 Component: Core Libraries | Version: 7.10.3 Resolution: | Keywords: newcomer Operating System: Linux | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: readLitChar Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2391 Wiki Page: | -------------------------------------+------------------------------------- Changes (by thomie): * cc: ekmett (added) * status: new => patch * differential: D2391 => Phab:D2391 * component: libraries/base => Core Libraries * milestone: => 8.2.1 Comment: Could someone from the CLC review Phad:D2391 please. Thanks. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 7 13:05:30 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 07 Jul 2016 13:05:30 -0000 Subject: [GHC] #12162: Concatenation of type level symbols missing In-Reply-To: <047.a39dfecb4a77da1ac163d250ec666f55@haskell.org> References: <047.a39dfecb4a77da1ac163d250ec666f55@haskell.org> Message-ID: <062.aba91a88fb75d9f4171f1840d6391e5b@haskell.org> #12162: Concatenation of type level symbols missing -------------------------------------+------------------------------------- Reporter: augustss | Owner: 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 thomie): * status: closed => new * resolution: duplicate => -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 7 13:59:52 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 07 Jul 2016 13:59:52 -0000 Subject: [GHC] #12181: Multi-threaded code on ARM64 GHC runtime doesn't use all available cores In-Reply-To: <045.62ec1d1031a2707c97a15db7c0ee2c82@haskell.org> References: <045.62ec1d1031a2707c97a15db7c0ee2c82@haskell.org> Message-ID: <060.36a77d9ed3581b474fc1fa9459f2d410@haskell.org> #12181: Multi-threaded code on ARM64 GHC runtime doesn't use all available cores --------------------------------------------+------------------------------ Reporter: varosi | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Runtime System | Version: 7.10.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: arm Type of failure: Runtime performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | --------------------------------------------+------------------------------ Comment (by varosi): The problem seems to be more deep. Currently we run a program written in C for profiling of matrix multiplication and it runs on all cores. When we run Haskell program with "+RTS -N8" (fix for number of cores) it runs 8 OS threads but they are taking just half of available cores and program runs much slower than running it with "+RTS -N4". This is the program for reference: https://bitbucket.org/varosi/cgraytrace/overview -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 7 14:17:55 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 07 Jul 2016 14:17:55 -0000 Subject: [GHC] #12181: Multi-threaded code on ARM64 GHC runtime doesn't use all available cores In-Reply-To: <045.62ec1d1031a2707c97a15db7c0ee2c82@haskell.org> References: <045.62ec1d1031a2707c97a15db7c0ee2c82@haskell.org> Message-ID: <060.8f95ce6d0c09962b3a3da89052ec94c4@haskell.org> #12181: Multi-threaded code on ARM64 GHC runtime doesn't use all available cores --------------------------------------------+------------------------------ Reporter: varosi | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Runtime System | Version: 7.10.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: arm Type of failure: Runtime performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | --------------------------------------------+------------------------------ Comment (by varosi): @thomie, yes, initially this 4 core machine is reporting only 1 active core. And as @rwbarton said, it is not a problem of GHC. So -N will not work correctly on that machine and we have to tell it explicitly 4 cores. It is actually tablet machine, so it save power with turning off cores. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 7 14:46:32 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 07 Jul 2016 14:46:32 -0000 Subject: [GHC] #4012: Compilation results are not deterministic In-Reply-To: <043.9c3dc141e8901acb12e4d7c1e6038096@haskell.org> References: <043.9c3dc141e8901acb12e4d7c1e6038096@haskell.org> Message-ID: <058.a18149d64a274b6e63b77f78d419f215@haskell.org> #4012: Compilation results are not deterministic -------------------------------------+------------------------------------- Reporter: kili | Owner: niteria Type: bug | Status: new Priority: high | Milestone: 8.2.1 Component: Compiler | Version: 6.12.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Other | Test Case: Blocked By: 11362 | Blocking: 12262 Related Tickets: #10424 | Differential Rev(s): Phab:D910, | Phab:D1073, Phab:D1133, Phab:D1192, | Phab:D1268, Phab:D1360, Phab:D1373, Wiki Page: | Phab:D1396, Phab:D1457, Phab:D1468, DeterministicBuilds | Phab:D1487, Phab:D1504, Phab:D1508 -------------------------------------+------------------------------------- Comment (by Bartosz Nitka ): In [changeset:"9858552d607f643db0385be2133a04dd4b5ff753/ghc" 9858552d/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="9858552d607f643db0385be2133a04dd4b5ff753" Use deterministic maps for FamInstEnv We turn FamInstEnvs into lists in some places which don't directly affect the ABI. That happens in family consistency checks and when producing output for `:info`. Unfortunately that nondeterminism is nonlocal and it's hard to tell locally what it affects. Furthermore the envs should be relatively small, so it should be free to use deterministic maps here. Testing with nofib and ./validate detected no difference between UniqFM and UniqDFM. GHC Trac: #4012 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 7 14:46:52 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 07 Jul 2016 14:46:52 -0000 Subject: [GHC] #12373: Type error but types match In-Reply-To: <043.bd1a92d82c4b4533b5d9ddee0a7fc4ab@haskell.org> References: <043.bd1a92d82c4b4533b5d9ddee0a7fc4ab@haskell.org> Message-ID: <058.0fcae95708baf173fcce432b34ae86cb@haskell.org> #12373: Type error but types match -------------------------------------+------------------------------------- Reporter: osa1 | Owner: Type: bug | Status: new Priority: normal | Milestone: 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: | -------------------------------------+------------------------------------- Comment (by simonpj): Yes, well spotted. It would be great to nail this since it keeps popping up. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 7 15:11:24 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 07 Jul 2016 15:11:24 -0000 Subject: [GHC] #12146: syntax repair suggestion is too eager to suggest TemplateHaskell In-Reply-To: <049.ae34cc16e6637ea2bb94449efc0751c9@haskell.org> References: <049.ae34cc16e6637ea2bb94449efc0751c9@haskell.org> Message-ID: <064.06d28d8462c10d7836c677e92cc3ec44@haskell.org> #12146: syntax repair suggestion is too eager to suggest TemplateHaskell -------------------------------------+------------------------------------- Reporter: j.waldmann | Owner: Type: feature request | 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: #7396 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Thomas Miedema ): In [changeset:"34085b501d99bd0b185a4addb0577330fa1f8356/ghc" 34085b50/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="34085b501d99bd0b185a4addb0577330fa1f8356" Correct the message displayed for syntax error (#12146) }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 7 15:12:20 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 07 Jul 2016 15:12:20 -0000 Subject: [GHC] #4012: Compilation results are not deterministic In-Reply-To: <043.9c3dc141e8901acb12e4d7c1e6038096@haskell.org> References: <043.9c3dc141e8901acb12e4d7c1e6038096@haskell.org> Message-ID: <058.ec751749a7bed75720347bc119c268e0@haskell.org> #4012: Compilation results are not deterministic -------------------------------------+------------------------------------- Reporter: kili | Owner: niteria Type: bug | Status: new Priority: high | Milestone: 8.2.1 Component: Compiler | Version: 6.12.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Other | Test Case: Blocked By: 11362 | Blocking: 12262 Related Tickets: #10424 | Differential Rev(s): Phab:D910, | Phab:D1073, Phab:D1133, Phab:D1192, | Phab:D1268, Phab:D1360, Phab:D1373, Wiki Page: | Phab:D1396, Phab:D1457, Phab:D1468, DeterministicBuilds | Phab:D1487, Phab:D1504, Phab:D1508 -------------------------------------+------------------------------------- Comment (by Bartosz Nitka ): In [changeset:"64bce8c31450d846cf1a1ca4ff31ec6c724f2e46/ghc" 64bce8c3/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="64bce8c31450d846cf1a1ca4ff31ec6c724f2e46" Add Note [FamInstEnv determinism] I'm just turning previous commit message into a Note GHC Trac: #4012 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 7 15:20:30 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 07 Jul 2016 15:20:30 -0000 Subject: [GHC] #12146: syntax repair suggestion is too eager to suggest TemplateHaskell In-Reply-To: <049.ae34cc16e6637ea2bb94449efc0751c9@haskell.org> References: <049.ae34cc16e6637ea2bb94449efc0751c9@haskell.org> Message-ID: <064.f7d07e4615cf745af6e17a2a4ebc3966@haskell.org> #12146: syntax repair suggestion is too eager to suggest TemplateHaskell -------------------------------------+------------------------------------- Reporter: j.waldmann | Owner: Type: feature request | 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: #7396 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by thomie): adityadivekar: I pushed the first two patches, but the last one did not apply cleanly to HEAD. The testcase also seems unnecessarily complicated (I guess you copied it from another test, but I don't understand why this hack is necessary): {{{ :set -v1 System.IO.writeFile "T12146.hs" "module Main where { ipmort Data.Char; }" -- hack: avoid the need for sleep by using specific timestamps: :! touch -t 01010000 T12146.hs :load T12146 }}} Two things are still missing: * a simple `compile_fail` test. Use `T4042` as an example. * a small comment for `badImplicitSplice` (`compiler/rename/RnSource.hs`), explaining why the error messages shouldn't mention `TemplateHaskell`, referring to this ticket (#12146). If you could, please create a new patch for this, and I'll apply it. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 7 19:51:54 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 07 Jul 2016 19:51:54 -0000 Subject: [GHC] #12372: bug: documentation for Control.Monad.guard not useful after AMP In-Reply-To: <043.bd49d884aa9da8caf539111086601a3f@haskell.org> References: <043.bd49d884aa9da8caf539111086601a3f@haskell.org> Message-ID: <058.bd2040c178233124afbc3ca247fd2840@haskell.org> #12372: bug: documentation for Control.Monad.guard not useful after AMP -------------------------------------+------------------------------------- Reporter: ntc2 | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: libraries/base | 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: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by ntc2): Replying to [comment:2 ekmett]: > Do you have an example of the text you'd prefer? Not off the top of my head. I'll think about this and get back to you. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 8 02:17:13 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 08 Jul 2016 02:17:13 -0000 Subject: [GHC] #12374: Type holes show incorrect type in GHCi Message-ID: <047.727762121a62e9f919571e3007cdeb58@haskell.org> #12374: Type holes show incorrect type in GHCi -------------------------------------+------------------------------------- Reporter: crockeea | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: GHCi | Version: 8.0.1 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: Incorrect Unknown/Multiple | warning at compile-time Test Case: | Blocked By: Blocking: | Related Tickets: 9479, 9091 Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- In a fresh GHCi: {{{ > show _ :7:6: error: • Found hole: _h :: () Or perhaps ‘_h’ is mis-spelled, or not in scope • In the first argument of ‘show’, namely ‘_h’ In the expression: show _h In an equation for ‘it’: it = show _h • Relevant bindings include it :: String (bound at :7:1) }}} This seems wrong: the type of the hole is `_h :: Show a0 => a0`, not `_h :: ()`. On a related note, should this be reporting two errors (one for the hole, one for the constraint) as in #9479? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 8 08:53:43 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 08 Jul 2016 08:53:43 -0000 Subject: [GHC] #12374: Type holes show incorrect type in GHCi In-Reply-To: <047.727762121a62e9f919571e3007cdeb58@haskell.org> References: <047.727762121a62e9f919571e3007cdeb58@haskell.org> Message-ID: <062.011c77b061b0e35077121c28aad4bc9a@haskell.org> #12374: Type holes show incorrect type in GHCi -------------------------------------+------------------------------------- Reporter: crockeea | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: GHCi | Version: 8.0.1 Resolution: invalid | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: 9479, 9091 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * status: new => closed * resolution: => invalid Comment: GHCi has type-class defaulting rules, described [http://downloads.haskell.org/~ghc/master/users-guide/ghci.html#type- defaulting-in-ghci here in the manual]. I think that's all that is happening here, so it's working as specified. Maybe the specification isn't right, but defaulting `Show` to `()` was driven by examples like {{{ > show [] }}} I'll close as invalid for now. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 8 09:47:52 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 08 Jul 2016 09:47:52 -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.c98caa123813b819a96967fca1489a3f@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 maeder): Replying to [comment:27 goldfire]: > Replying to [comment:22 simonpj]: > > I'm one of those who thinks that the fact that `f R { x = e }` means `f (R { x = e })` is a mistake :-). > > > > I agree with you here, but I think the proposal in this ticket is still sensible, given that the perhaps-unexpected parsing started with a keyword. In the record update case, the perhaps-unexpected parsing isn't known until the open-brace, even though your brain has to parse the preceding space differently. To me, that's the real problem with the parsing of record-update: it's not left-to-right. I fully agree, too! The record syntax is unrelated to this proposal. Curly record braces are sort of a strong binding postfix operator and are thus different from plain parentheses. @aiko I would omit the point "This would make do blocks consistent with record creation ..." under Pros on https://ghc.haskell.org/trac/ghc/wiki/ArgumentDo. Record creation is only another kind of a more "non-atomic" aexp in the grammar. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 8 10:02:03 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 08 Jul 2016 10:02:03 -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.6c61dec77923489fb71f58a6424df919@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 maeder): @aiko I also agree fully with Richard Eisenberg and do not understand your objection. Therefore I would like if you could add "it makes the language more regular" under Pros, omitted your last paragraph, and really simplified the proposed grammar rules accordingly (namely without lexp and openexp) on ArgumentDo. (For a discussion/omission of group A and group B constructs I refer to https://mail.haskell.org/pipermail/glasgow-haskell- users/2016-July/026299.html) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 8 10:22:53 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 08 Jul 2016 10:22:53 -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.0f8339b7edaa9c30267474cf2fa4b0e7@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 maeder): By saying "curly record braces are sort of a strongly binding postfix operator" I suggest that it would also possible to allow, i.e. "R {...} {...}" as nested record updates (but that would be a different issues). The keywords, do, \, case, etc. in this proposal, however, are IMHO best characterized as weakly binding prefix operators (and I completely ignore curly layout braces here on purpose - I hardly use them). -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 8 11:04:21 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 08 Jul 2016 11:04:21 -0000 Subject: [GHC] #4012: Compilation results are not deterministic In-Reply-To: <043.9c3dc141e8901acb12e4d7c1e6038096@haskell.org> References: <043.9c3dc141e8901acb12e4d7c1e6038096@haskell.org> Message-ID: <058.9c1115edc5bc41773478f8d52de094d8@haskell.org> #4012: Compilation results are not deterministic -------------------------------------+------------------------------------- Reporter: kili | Owner: niteria Type: bug | Status: new Priority: high | Milestone: 8.2.1 Component: Compiler | Version: 6.12.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Other | Test Case: Blocked By: 11362 | Blocking: 12262 Related Tickets: #10424 | Differential Rev(s): Phab:D910, | Phab:D1073, Phab:D1133, Phab:D1192, | Phab:D1268, Phab:D1360, Phab:D1373, Wiki Page: | Phab:D1396, Phab:D1457, Phab:D1468, DeterministicBuilds | Phab:D1487, Phab:D1504, Phab:D1508 -------------------------------------+------------------------------------- Comment (by Bartosz Nitka ): In [changeset:"04813246f2279bbdb4dc3c268b98f097c62d098b/ghc" 04813246/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="04813246f2279bbdb4dc3c268b98f097c62d098b" Use UniqDFM for InstEnv Rationale in the comment. Also updates submodule array with test output changes. GHC Trac: #4012 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 8 14:09:34 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 08 Jul 2016 14:09:34 -0000 Subject: [GHC] #9091: print and/or apply constraints when showing info for typed holes In-Reply-To: <047.d95c0766523b082befd3b58cd013d678@haskell.org> References: <047.d95c0766523b082befd3b58cd013d678@haskell.org> Message-ID: <062.5de7e4ab49a56054641146fa573f08ef@haskell.org> #9091: print and/or apply constraints when showing info for typed holes -------------------------------------+------------------------------------- Reporter: kosmikus | Owner: 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: #9479 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by dfeuer): I think part of this was fixed with #9479, but I don't know if the constraints on the relevant bindings (the "easy" part) were included. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 8 14:09:34 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 08 Jul 2016 14:09:34 -0000 Subject: [GHC] #11717: Way to dump cmm only once In-Reply-To: <046.147581339d89f71c221c940bc7bdc90a@haskell.org> References: <046.147581339d89f71c221c940bc7bdc90a@haskell.org> Message-ID: <061.0bc3610c62f6effc522b4beca9cd909a@haskell.org> #11717: Way to dump cmm only once -------------------------------------+------------------------------------- Reporter: nomeata | Owner: tvv Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.1 (CodeGen) | 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 tvv): * owner: => tvv -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 8 14:12:41 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 08 Jul 2016 14:12:41 -0000 Subject: [GHC] #12357: Increasing maximum constraint tuple size significantly blows up compiler allocations In-Reply-To: <046.dd0f12e974ac3c5c9febd70397bf4138@haskell.org> References: <046.dd0f12e974ac3c5c9febd70397bf4138@haskell.org> Message-ID: <061.66d5ce8a1bd4b782fb00b5c0e19a278b@haskell.org> #12357: Increasing maximum constraint tuple size significantly blows up compiler allocations -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.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): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"eb3d6595735671605c5d6294a796dc0f16f784a4/ghc" eb3d6595/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="eb3d6595735671605c5d6294a796dc0f16f784a4" OccName: Avoid re-encoding derived OccNames Previously we would form derived OccNames by first decoding the name being derived from, manipulating it in [Char] form, and then re-encoding. This is all very wasteful as we essentially always just want to concatenate. Instead we now take care to form the final name with only one concatFS. Test Plan: Validate, examing compiler allocations Reviewers: simonpj, austin Reviewed By: simonpj Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2387 GHC Trac Issues: #12357 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 8 14:17:10 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 08 Jul 2016 14:17:10 -0000 Subject: [GHC] #12375: type synonym to unboxed tuple causes crash Message-ID: <043.ec186c470be76b29348c4afe9786397d@haskell.org> #12375: type synonym to unboxed tuple causes crash -------------------------------------+------------------------------------- Reporter: osa1 | Owner: 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: -------------------------------------+------------------------------------- {{{#!haskell {-# LANGUAGE UnboxedTuples #-} module Main where -- type Null = (# #) {-# NOINLINE showNull #-} showNull :: (# #) -> String showNull (# #) = "(# #)" {-# NOINLINE showNullPair #-} showNullPair :: (# (# #), (# #) #) -> String showNullPair (# n1, n2 #) = "(# " ++ showNull n1 ++ ", " ++ showNull n2 ++ "#)" main :: IO () main = do putStrLn (showNullPair (# (# #), (# #) #)) }}} If I use the `Null` type synonym here instead of `(# #)`, I get: {{{ [1 of 1] Compiling Main ( empty.hs, empty.o ) ghc: panic! (the 'impossible' happened) (GHC version 8.0.1 for x86_64-unknown-linux): unboxed tuple PrimRep Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug }}} Tried with: 8.0.1 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 8 14:57:12 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 08 Jul 2016 14:57:12 -0000 Subject: [GHC] #4012: Compilation results are not deterministic In-Reply-To: <043.9c3dc141e8901acb12e4d7c1e6038096@haskell.org> References: <043.9c3dc141e8901acb12e4d7c1e6038096@haskell.org> Message-ID: <058.56aa268c3406b44386421893a2061224@haskell.org> #4012: Compilation results are not deterministic -------------------------------------+------------------------------------- Reporter: kili | Owner: niteria Type: bug | Status: new Priority: high | Milestone: 8.2.1 Component: Compiler | Version: 6.12.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Other | Test Case: Blocked By: 11362 | Blocking: 12262 Related Tickets: #10424 | Differential Rev(s): Phab:D910, | Phab:D1073, Phab:D1133, Phab:D1192, | Phab:D1268, Phab:D1360, Phab:D1373, Wiki Page: | Phab:D1396, Phab:D1457, Phab:D1468, DeterministicBuilds | Phab:D1487, Phab:D1504, Phab:D1508 -------------------------------------+------------------------------------- Comment (by Bartosz Nitka ): In [changeset:"4f21a518d10abff786794cda086da0474971cdf9/ghc" 4f21a51/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="4f21a518d10abff786794cda086da0474971cdf9" Kill eltsUFM in classifyTyCons GHC Trac: #4012 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 8 15:18:02 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 08 Jul 2016 15:18:02 -0000 Subject: [GHC] #11717: Way to dump cmm only once In-Reply-To: <046.147581339d89f71c221c940bc7bdc90a@haskell.org> References: <046.147581339d89f71c221c940bc7bdc90a@haskell.org> Message-ID: <061.e9bf278644b3fcc5c822bad1cdd63e80@haskell.org> #11717: Way to dump cmm only once -------------------------------------+------------------------------------- Reporter: nomeata | Owner: tvv Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.1 (CodeGen) | 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:D2393 Wiki Page: | -------------------------------------+------------------------------------- Changes (by tvv): * differential: => Phab:D2393 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 8 18:20:52 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 08 Jul 2016 18:20:52 -0000 Subject: [GHC] #9625: ghc: panic using --enable-executable-dynamic In-Reply-To: <051.41ace47270d90cc9e836ab3706638147@haskell.org> References: <051.41ace47270d90cc9e836ab3706638147@haskell.org> Message-ID: <066.6ca4a7aaec0024ac8a94ea976d3982b2@haskell.org> #9625: ghc: panic using --enable-executable-dynamic -------------------------------------+------------------------------------- Reporter: CoreyOConnor | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Package system | Version: 7.8.3 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by thomie): * status: new => closed * resolution: => fixed Comment: With Cabal-1.24.0.0, the panic is gone, but the test ends with `read: no parse`. I have a fix for that in https://github.com/haskell/cabal/pull/3527. Closing this ticket here, as it is a Cabal issue now. > Is there any other reason for the convention that Haskell library names start with HS? Is this convention documented anywhere? I have no idea. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 8 18:45:05 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 08 Jul 2016 18:45:05 -0000 Subject: [GHC] #12209: Windows: ByteCodeLink can't find labels "lseek" and "write" In-Reply-To: <045.975f9511f81812044ea05b78c5c3a0b0@haskell.org> References: <045.975f9511f81812044ea05b78c5c3a0b0@haskell.org> Message-ID: <060.66121fb857938e6f55fe68648c0f11ac@haskell.org> #12209: Windows: ByteCodeLink can't find labels "lseek" and "write" -------------------------------------+------------------------------------- Reporter: thomie | Owner: Type: bug | Status: new Priority: normal | Milestone: 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: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Phyx-): `lseek` and `write` existed before Microsoft deprecated the POSIX functions. As such, they did used to exist https://msdn.microsoft.com/en- us/library/ms235323.aspx During `WAY=ghci` we query `msvcrt.dll` directly which is the C runtime. The function has been deprecated long enough that it's been removed. {{{ e:\temp\dynamic>dumpbin /exports c:\Windows\System32\msvcrt.dll | findstr lseek 496 1EF 0001D080 _lseek = _lseek 497 1F0 0001D230 _lseeki64 = _lseeki64 e:\temp\dynamic>dumpbin /exports c:\Windows\System32\msvcrt.dll | findstr write 998 3E5 0001FA20 _write = _write 1113 458 0004DB90 fwrite = fwrite }}} During linking, `Mingw-w64` ends up linking against the import library `msvcrt.a` which contains a redirect from `lseek` to `_lseek`. Probably for backwards compatibility. {{{ $ nm -s "inplace\mingw\x86_64-w64-mingw32\lib\libmsvcrt.a" | grep lseek _lseeki64 in dcnfs00450.o __imp__lseeki64 in dcnfs00450.o _lseek in dcnfs00449.o __imp__lseek in dcnfs00449.o lseek in dcnfs00448.o __imp_lseek in dcnfs00448.o 0000000000000000 I __imp__lseeki64 0000000000000000 T _lseeki64 0000000000000000 I __imp__lseek 0000000000000000 T _lseek 0000000000000000 I __imp_lseek 0000000000000000 T lseek }}} So the correct solution would be to use the `_` versions. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 8 20:12:17 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 08 Jul 2016 20:12:17 -0000 Subject: [GHC] #10311: package name returned from tyConPackage is garbled In-Reply-To: <049.befe981d27d5c4c24d07557f283ecb8b@haskell.org> References: <049.befe981d27d5c4c24d07557f283ecb8b@haskell.org> Message-ID: <064.47a71914b6b866f4d44170a0d1cb9170@haskell.org> #10311: package name returned from tyConPackage is garbled -------------------------------------+------------------------------------- Reporter: j.waldmann | Owner: ezyang Type: bug | Status: new Priority: normal | Milestone: Component: Package system | Version: 7.10.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 j.waldmann): So this was fixed in ghc-8.0.1? By chance I found that the test case from the ticket now does return "containers-0.5.7.1". -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 8 20:38:21 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 08 Jul 2016 20:38:21 -0000 Subject: [GHC] #12357: Increasing maximum constraint tuple size significantly blows up compiler allocations In-Reply-To: <046.dd0f12e974ac3c5c9febd70397bf4138@haskell.org> References: <046.dd0f12e974ac3c5c9febd70397bf4138@haskell.org> Message-ID: <061.fb6119ca16cf1531a30693d7cc03cbfb@haskell.org> #12357: Increasing maximum constraint tuple size significantly blows up compiler allocations -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.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): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"6c7c193f376fe3b48992724c12f6ff393dca6528/ghc" 6c7c193/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="6c7c193f376fe3b48992724c12f6ff393dca6528" DsExpr: Remove usage of concatFS in fingerprintName This was the only user of concatFS and really just wants the `String` anyways. Stumbled upon while looking at #12357. Test Plan: Validate Reviewers: austin Reviewed By: austin Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2386 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 8 20:54:05 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 08 Jul 2016 20:54:05 -0000 Subject: [GHC] #12375: type synonym to unboxed tuple causes crash In-Reply-To: <043.ec186c470be76b29348c4afe9786397d@haskell.org> References: <043.ec186c470be76b29348c4afe9786397d@haskell.org> Message-ID: <058.d7001979b6efa841d99bbd17f79b037d@haskell.org> #12375: type synonym to unboxed tuple causes crash -------------------------------------+------------------------------------- Reporter: osa1 | Owner: 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 osa1): This is fixed in my unboxed sums branch which I'm hoping to merge this week. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 8 22:22:00 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 08 Jul 2016 22:22:00 -0000 Subject: [GHC] #10311: package name returned from tyConPackage is garbled In-Reply-To: <049.befe981d27d5c4c24d07557f283ecb8b@haskell.org> References: <049.befe981d27d5c4c24d07557f283ecb8b@haskell.org> Message-ID: <064.9306fda27b54348ea349062bd1e808dc@haskell.org> #10311: package name returned from tyConPackage is garbled -------------------------------------+------------------------------------- Reporter: j.waldmann | Owner: ezyang Type: bug | Status: new Priority: normal | Milestone: Component: Package system | Version: 7.10.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): j.waldmann: In a sense. Because of tickets like this, we brought back the long-form version of the Cabal name (so package name plus version). But *technically* the string is still supposed to be opaque and we are still supposed to give you facilities for getting the package name and version. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jul 9 00:23:28 2016 From: ghc-devs at haskell.org (GHC) Date: Sat, 09 Jul 2016 00:23:28 -0000 Subject: [GHC] #12376: Allow function definitions in record syntax Message-ID: <051.ff1dad08610f3c1f3808a2894d40fdae@haskell.org> #12376: Allow function definitions in record syntax -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: feature | Status: new request | 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: -------------------------------------+------------------------------------- Would it be possible to write {{{#!hs propertyMap :: (Monad m, Ord k) => v -> PropertyMap m k v propertyMap v0 = go v0 Map.empty where go v m = PropertyMap { getP = \k -> return $ maybe v id (Map.lookup k m) , putP = \k v' -> return $ go v (Map.insert k v' m) } }}} as {{{#!hs propertyMap :: (Monad m, Ord k) => v -> PropertyMap m k v propertyMap v0 = go v0 Map.empty where go v m = PropertyMap { getP k = return $ maybe v id (Map.lookup k m) , putP k v' = return $ go v (Map.insert k v' m) } }}} Simpler example `MkFoo { id = \x -> x }` as {{{#!hs MkFoo { id x = x } }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jul 9 00:23:47 2016 From: ghc-devs at haskell.org (GHC) Date: Sat, 09 Jul 2016 00:23:47 -0000 Subject: [GHC] #12376: Allow function definitions in record syntax In-Reply-To: <051.ff1dad08610f3c1f3808a2894d40fdae@haskell.org> References: <051.ff1dad08610f3c1f3808a2894d40fdae@haskell.org> Message-ID: <066.24eeae7df35e2eb78f7bf02f8776dbd7@haskell.org> #12376: Allow function definitions in record syntax -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: 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: | -------------------------------------+------------------------------------- Comment (by Iceland_jack): Motivating example from [https://hackage.haskell.org/package/graphs-0.7/docs/src/Data-Graph- PropertyMap.html Data.Graph.PropertyMap] -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jul 9 00:47:27 2016 From: ghc-devs at haskell.org (GHC) Date: Sat, 09 Jul 2016 00:47:27 -0000 Subject: [GHC] #12240: Common Sense for Type Classes In-Reply-To: <050.3dcf7ad3ce6a480cdc5fe8435e755275@haskell.org> References: <050.3dcf7ad3ce6a480cdc5fe8435e755275@haskell.org> Message-ID: <065.0c10b66fad377100341c8ec1ef97954e@haskell.org> #12240: Common Sense for Type Classes -------------------------------------+------------------------------------- Reporter: Mathnerd314 | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 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 ezyang): Mathnerd314: For what it's worth, I think this is a very interesting proposal, and merits further investigation. Let me consider a slightly modified version of your original example: {{{ {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE FlexibleContexts #-} module T4921 where class C a b where f :: a -> b instance C Int Char where f = undefined g x = f (x :: Int) }}} What should the inferred type of `g` be? There seem to be two options: 1. `g :: C Int b => Int -> b`, which is the current behavior of GHC today. The reasoning goes like this, "While it is true that there is only one instance of C where a ~ Int today, in some later module someone could very well define `C Int Int`, in which case, egg on my face if I picked the original instance! Better leave it to the user of `g` to tell me which one they actually want." 2. `g :: Int -> Char`, which I believe is what you are proposing. The reasoning here is, "Well, based on the instances I can see, it's BLOODY WELL obvious that the only possible instance `f` could use is `C a b`. The resolution is unambiguous." In most cases, option (1) makes more programs typecheck, EXCEPT when there could be ambiguity, in which case the more specific type is desirable; e.g. if I say `show (g 2)` (what am I showing? With the instances I can see, the only thing possible is `Char`.) Actually, there is mechanism for dealing with this situation: defaulting. In Haskell98, the `default` declaration is a way of saying, "When I get an ambiguous type, please pluck out this type to solve the ambiguity and then go your merry way." What your proposal seems to suggest is an alternate way to do defaulting, by consulting the instance environment in question. Specifically, if I have an ambiguous type variable `v` which occurs in some class `C t1 v ...`, if there is only ONE choice of `v` which allows the instance resolution to go through, I should default `v` to that one! This would (also) solve the original problem in your ticket. But maybe you have an example where you wanted more specific instance resolution, even in the absence of ambiguity. I'd be quite interested to see it. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jul 9 02:06:09 2016 From: ghc-devs at haskell.org (GHC) Date: Sat, 09 Jul 2016 02:06:09 -0000 Subject: [GHC] #12234: 'deriving Eq' on recursive datatype makes ghc eat a lot of CPU and RAM In-Reply-To: <045.352c8bb25c33b092176709513059d519@haskell.org> References: <045.352c8bb25c33b092176709513059d519@haskell.org> Message-ID: <060.3a4359b9f04120abb3bcc4c1a04c0e4a@haskell.org> #12234: 'deriving Eq' on recursive datatype makes ghc eat a lot of CPU and RAM -------------------------------------+------------------------------------- Reporter: slyfox | Owner: 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 vladki): Just in case, removing one of the parameters in the `ExprF` constructor makes the problem go away: {{{ data ExprF rT = ExprF rT deriving Eq }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jul 9 06:21:40 2016 From: ghc-devs at haskell.org (GHC) Date: Sat, 09 Jul 2016 06:21:40 -0000 Subject: [GHC] #12146: syntax repair suggestion is too eager to suggest TemplateHaskell In-Reply-To: <049.ae34cc16e6637ea2bb94449efc0751c9@haskell.org> References: <049.ae34cc16e6637ea2bb94449efc0751c9@haskell.org> Message-ID: <064.47b2d705d1f94dcdb16e5d396d27565a@haskell.org> #12146: syntax repair suggestion is too eager to suggest TemplateHaskell -------------------------------------+------------------------------------- Reporter: j.waldmann | Owner: Type: feature request | 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: #7396 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by adityadivekar): Yes, I realised that the hack was unnecessary. I'm sorry for that. I've simplified it now. And I've created two new patches - one containing the comment about `badImplicitSplice`, and the other containing the two test cases. I thought it would be confusing to put them in one patch, so I split them. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jul 9 06:22:08 2016 From: ghc-devs at haskell.org (GHC) Date: Sat, 09 Jul 2016 06:22:08 -0000 Subject: [GHC] #12146: syntax repair suggestion is too eager to suggest TemplateHaskell In-Reply-To: <049.ae34cc16e6637ea2bb94449efc0751c9@haskell.org> References: <049.ae34cc16e6637ea2bb94449efc0751c9@haskell.org> Message-ID: <064.b9bd07f8e9059ecc5e4daf296e3bdcd0@haskell.org> #12146: syntax repair suggestion is too eager to suggest TemplateHaskell -------------------------------------+------------------------------------- Reporter: j.waldmann | Owner: Type: feature request | 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: #7396 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by adityadivekar): * Attachment "0001-Add-comment-explaining-change-in-syntax-error- sugges.patch" added. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jul 9 06:22:18 2016 From: ghc-devs at haskell.org (GHC) Date: Sat, 09 Jul 2016 06:22:18 -0000 Subject: [GHC] #12146: syntax repair suggestion is too eager to suggest TemplateHaskell In-Reply-To: <049.ae34cc16e6637ea2bb94449efc0751c9@haskell.org> References: <049.ae34cc16e6637ea2bb94449efc0751c9@haskell.org> Message-ID: <064.c112732bbbfcbd8c7a166f12223df8ef@haskell.org> #12146: syntax repair suggestion is too eager to suggest TemplateHaskell -------------------------------------+------------------------------------- Reporter: j.waldmann | Owner: Type: feature request | 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: #7396 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by adityadivekar): * Attachment "0001-Add-test-cases-for-Ticket-12146.patch" added. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jul 9 07:13:22 2016 From: ghc-devs at haskell.org (GHC) Date: Sat, 09 Jul 2016 07:13:22 -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.e3a9d946d49b407f466be9ac92abca41@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 maeder): @aiko The Cons point "You can already get rid of the $ by just adding parentheses" is only an argument against "$" (or the title of this issue) but not against ArgumentDo. It is actually a Pros point: Allow to get rid of parentheses without using the $-workaround. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jul 9 11:36:15 2016 From: ghc-devs at haskell.org (GHC) Date: Sat, 09 Jul 2016 11:36:15 -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.614f76ea9b311829b2727c215691804a@haskell.org> #11758: Drop x86_64 binutils <2.17 hack -------------------------------------+------------------------------------- Reporter: bgamari | Owner: avd Type: task | Status: new Priority: normal | Milestone: 8.2.1 Component: Compiler (NCG) | Version: 8.0.1-rc2 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 avd): * owner: => avd -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jul 9 16:16:28 2016 From: ghc-devs at haskell.org (GHC) Date: Sat, 09 Jul 2016 16:16:28 -0000 Subject: [GHC] #12231: Eliminate redundant heap allocations/deallocations In-Reply-To: <047.2bb733afa458793dc239cf6b3bd50652@haskell.org> References: <047.2bb733afa458793dc239cf6b3bd50652@haskell.org> Message-ID: <062.566e1021ea233b263ca3339b9ac4a035@haskell.org> #12231: Eliminate redundant heap allocations/deallocations -------------------------------------+------------------------------------- Reporter: harendra | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 (CodeGen) | 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 michalt): * cc: michalt (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jul 9 16:44:56 2016 From: ghc-devs at haskell.org (GHC) Date: Sat, 09 Jul 2016 16:44:56 -0000 Subject: [GHC] #10923: GHC should recompile if flags change In-Reply-To: <045.701a073c5a04ad8846380b456c6613ef@haskell.org> References: <045.701a073c5a04ad8846380b456c6613ef@haskell.org> Message-ID: <060.ee6adc536a5f685e91f487ce943b8e78@haskell.org> #10923: GHC should recompile if flags change -------------------------------------+------------------------------------- Reporter: ezyang | Owner: Type: bug | Status: new Priority: low | Milestone: Component: Compiler | Version: 7.10.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 thomie): * cc: simonmar (added) Comment: simonmar: you wrote in ticket:437#comment:18 (5 years ago): > It's not clear to me that changing optimisation settings should trigger recompilation: for example, you might have a large program compiled unoptimised, and then decide that you want to optimise just one or two modules, so you remove a few .o files, add -O and recompile. But these GHC users recently expressed their confusion about the current behavior: * #haskell user mtesseract: > Isn't stack supposed to rebuild a package when I specify a new set of ghc-options on the command line? As in e.g. 'stack build --ghc- options=-O0'? It doesn't seem to rebuild anything here, irregardles of the ghc-options I specify. * reddit user [https://www.reddit.com/r/haskell/comments/4ro749/help_cabal_and_ghc_optimzation_flag_questions/ winterland1989]: > when I change my own project's cabal from none to -O2, nothing will be recompiled, why? Shall we add optimization flags to `fingerprintDynFlags` in `compiler/iface/FlagChecker.hs`? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jul 9 16:50:23 2016 From: ghc-devs at haskell.org (GHC) Date: Sat, 09 Jul 2016 16:50:23 -0000 Subject: [GHC] #10923: GHC should recompile if flags change In-Reply-To: <045.701a073c5a04ad8846380b456c6613ef@haskell.org> References: <045.701a073c5a04ad8846380b456c6613ef@haskell.org> Message-ID: <060.1ced11d107dc2d424df0f86645673c00@haskell.org> #10923: GHC should recompile if flags change -------------------------------------+------------------------------------- Reporter: ezyang | Owner: Type: bug | Status: new Priority: low | Milestone: Component: Compiler | Version: 7.10.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): I am sure that there are some people who are using the old behavior. Maybe there needs to be a flag flipping between the two behaviors. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jul 9 17:00:06 2016 From: ghc-devs at haskell.org (GHC) Date: Sat, 09 Jul 2016 17:00:06 -0000 Subject: [GHC] #10923: GHC should recompile if flags change In-Reply-To: <045.701a073c5a04ad8846380b456c6613ef@haskell.org> References: <045.701a073c5a04ad8846380b456c6613ef@haskell.org> Message-ID: <060.75e1fa2245582e211bf954ea95ce11e5@haskell.org> #10923: GHC should recompile if flags change -------------------------------------+------------------------------------- Reporter: ezyang | Owner: Type: bug | Status: new Priority: low | Milestone: Component: Compiler | Version: 7.10.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 rwbarton): Like `-fforce-recomp`? Or do you mean "`-fno-force-recomp`" (not sure whether that already exists)? I probably have made use of the current behavior before, though adding an `OPTIONS_GHC` pragma to a subset of the files is also a possibility. I've much more often been annoyed by needing to add `-fforce-recomp` when comparing the same program at different optimization levels. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jul 9 21:30:43 2016 From: ghc-devs at haskell.org (GHC) Date: Sat, 09 Jul 2016 21:30:43 -0000 Subject: [GHC] #12363: Type application for infix In-Reply-To: <051.833fc99ca846ecc78974bf61eb05e05f@haskell.org> References: <051.833fc99ca846ecc78974bf61eb05e05f@haskell.org> Message-ID: <066.2bc47bd63f9dcede359731527bc46f20@haskell.org> #12363: Type application for infix -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: 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: | -------------------------------------+------------------------------------- Comment (by Iceland_jack): Replying to [comment:1 goldfire]: > -1 from me, sorry. I understand your -1. I will write examples that come to mind without pushing my point. I feel this has pedagogic value: {{{#!hs instance Eq a => Eq [a] where (==) :: [a] -> [a] -> Bool [] == [] = True (x:xs) == (y:ys) = x == y && xs == ys _ == _ = False }}} in the second equation `==` is called at two different types, wouldn't this be a beautiful way of showing that? {{{#!hs instance Eq a => Eq [a] where ... (x:xs) == (y:ys) = x == @a y && xs == @[a] ys }}} I'm no fan of the `foldMap` example. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jul 9 23:39:40 2016 From: ghc-devs at haskell.org (GHC) Date: Sat, 09 Jul 2016 23:39:40 -0000 Subject: [GHC] #12363: Type application for infix In-Reply-To: <051.833fc99ca846ecc78974bf61eb05e05f@haskell.org> References: <051.833fc99ca846ecc78974bf61eb05e05f@haskell.org> Message-ID: <066.8752cf42e1c18911fbe9896d0c1ef673@haskell.org> #12363: Type application for infix -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: 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: | -------------------------------------+------------------------------------- Comment (by Iceland_jack): It's reminiscent of math notation, for example homomorphisms: {{{#!hs instance Semigroup Int where (<>) = (+) }}} {{{#!hs -- |abc| ◇_ℕ |xyz| = |abc ◇_Σ∗ xyz| length "abc" <> @Int length "xyz" -- == length ("abc" <> @String "xyz") }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Jul 10 02:54:15 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 10 Jul 2016 02:54:15 -0000 Subject: [GHC] #12374: Type holes show incorrect type in GHCi In-Reply-To: <047.727762121a62e9f919571e3007cdeb58@haskell.org> References: <047.727762121a62e9f919571e3007cdeb58@haskell.org> Message-ID: <062.5cd12a9aad59b5ae8717a402507437e6@haskell.org> #12374: Type holes show incorrect type in GHCi -------------------------------------+------------------------------------- Reporter: crockeea | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: GHCi | Version: 8.0.1 Resolution: invalid | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: 9479, 9091 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Iceland_jack): Without defaulting {{{ GHCi, version 8.0.1: http://www.haskell.org/ghc/ :? for help defaulLoaded GHCi configuration from /home/baldur/.ghci ghci> default () ghci> show _ :2:1: error: • Ambiguous type variable ‘a0’ arising from a use of ‘show’ prevents the constraint ‘(Show a0)’ from being solved. Probable fix: use a type annotation to specify what ‘a0’ should be. These potential instances exist: instance Show a => Show (ZipList a) -- Defined in ‘Control.Applicative’ instance Show a => Show (Down a) -- Defined in ‘Data.Ord’ instance Show CallStack -- Defined in ‘GHC.Show’ ...plus 28 others ...plus 77 instances involving out-of-scope types (use -fprint-potential-instances to see them all) • In the expression: show _ In an equation for ‘it’: it = show _ :2:6: error: • Found hole: _ :: a0 Where: ‘a0’ is an ambiguous type variable • In the first argument of ‘show’, namely ‘_’ In the expression: show _ In an equation for ‘it’: it = show _ • Relevant bindings include it :: String (bound at :2:1) ghci> }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Jul 10 08:42:52 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 10 Jul 2016 08:42:52 -0000 Subject: [GHC] #12357: Increasing maximum constraint tuple size significantly blows up compiler allocations In-Reply-To: <046.dd0f12e974ac3c5c9febd70397bf4138@haskell.org> References: <046.dd0f12e974ac3c5c9febd70397bf4138@haskell.org> Message-ID: <061.f1abe4c76e3181803172257f578b50ce@haskell.org> #12357: Increasing maximum constraint tuple size significantly blows up compiler allocations -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.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): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"f53d761df9762232b54ec57a950d301011cd21f8/ghc" f53d761/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="f53d761df9762232b54ec57a950d301011cd21f8" TysWiredIn: Use UniqFM lookup for built-in OccNames Previously we would unpack the OccName into a String, then pattern match against this string. Due to the implementation of `unpackFS`, this actually unpacks the entire contents, even though we often only need to look at the first few characters. Here we take another approach: build a UniqFM with the known built-in OccNames, allowing us to use `FastString`'s hash-based comparison instead. Reviewers: simonpj, austin, simonmar Reviewed By: simonmar Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2385 GHC Trac Issues: #12357 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Jul 10 19:16:46 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 10 Jul 2016 19:16:46 -0000 Subject: [GHC] #12377: getExecutablePath doesn't return absolute path on OpenBSD (and maybe other OS also) Message-ID: <047.ce292d74547e5761ab80fddf4c2b76fa@haskell.org> #12377: getExecutablePath doesn't return absolute path on OpenBSD (and maybe other OS also) -------------------------------------+------------------------------------- Reporter: oherrala | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: | Version: 8.0.1 libraries/base | Keywords: | Operating System: OpenBSD Architecture: | Type of failure: Incorrect result Unknown/Multiple | at runtime Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- System.Environment.getExecutablePath doesn't return absolute path to executable in OpenBSD. This happens because getExecutablePath uses argv[0] to determine path and argv[0] might not be absolute path. My environment: {{{ $ uname -a OpenBSD fizbuz.pilkki.ciz.fi 6.0 GENERIC.MP#2274 amd64 $ ghc -V The Glorious Glasgow Haskell Compilation System, version 7.10.3 }}} This test program in OpenBSD: {{{#!hs module Main where import System.Environment main = getExecutablePath >>= print }}} returns {{{ $ ./test "./test" }}} For example in OS X the call returns absolute path: {{{ $ ./test "/Users/oherrala/tmp/test" }}} OpenBSD is one of the operating systems which gets fall back to using argv[0] to determine exec's location: https://git.haskell.org/ghc.git/blob/HEAD:/libraries/base/System/Environment/ExecutablePath.hsc#l152 Maybe the argv[0] result should be wrapped with realpath(3) to get absolute path? This bug is also present in cabal-install and reported here: https://github.com/haskell/cabal/issues/3512#issuecomment-231604356 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Jul 10 19:32:23 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 10 Jul 2016 19:32:23 -0000 Subject: [GHC] #12377: getExecutablePath doesn't return absolute path on OpenBSD (and maybe other OS also) In-Reply-To: <047.ce292d74547e5761ab80fddf4c2b76fa@haskell.org> References: <047.ce292d74547e5761ab80fddf4c2b76fa@haskell.org> Message-ID: <062.0479287deb65b7a97c4cee0eb6744f38@haskell.org> #12377: getExecutablePath doesn't return absolute path on OpenBSD (and maybe other OS also) -------------------------------------+------------------------------------- Reporter: oherrala | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: libraries/base | Version: 7.10.3 Resolution: | Keywords: Operating System: OpenBSD | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by oherrala): * version: 8.0.1 => 7.10.3 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Jul 10 20:41:38 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 10 Jul 2016 20:41:38 -0000 Subject: [GHC] #10923: GHC should recompile if flags change In-Reply-To: <045.701a073c5a04ad8846380b456c6613ef@haskell.org> References: <045.701a073c5a04ad8846380b456c6613ef@haskell.org> Message-ID: <060.7383de4f6492abc70c303d70cd80a9d8@haskell.org> #10923: GHC should recompile if flags change -------------------------------------+------------------------------------- Reporter: ezyang | Owner: Type: bug | Status: new Priority: low | Milestone: Component: Compiler | Version: 7.10.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 simonmar): Arguably it's wrong for GHC to say "ok, done" when the object file on disk is not the same as the one it would have produced if it had recompiled. (for some suitable definition of "the same"). So I'm ok with changing this, especially if it's confusing people. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 11 04:54:39 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 11 Jul 2016 04:54:39 -0000 Subject: [GHC] #12378: Not enough inlining happens with single-method type classes Message-ID: <043.6cfc5337b3b4cd84d2c9380280b0d202@haskell.org> #12378: Not enough inlining happens with single-method type classes -------------------------------------+------------------------------------- Reporter: akio | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 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: -------------------------------------+------------------------------------- In the attached file, GHC produces code (with `-O2`) for `foo` that references a top-level definition of type `Small (Either () ())`, despite the fact that all bindings in the module are marked INLINE. If I use `-DOTHER_METHOD` to add another method to the class, this problem goes away. It looks like a ClassOp rule is helping here. I'm not sure if this is a bug, but it was a surprising behavior for me, so I'm reporting it. Please feel free to close this ticket if it's the correct behavior. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 11 04:55:02 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 11 Jul 2016 04:55:02 -0000 Subject: [GHC] #12378: Not enough inlining happens with single-method type classes In-Reply-To: <043.6cfc5337b3b4cd84d2c9380280b0d202@haskell.org> References: <043.6cfc5337b3b4cd84d2c9380280b0d202@haskell.org> Message-ID: <058.6a4d58f1b56d019fe9886d22e2203e12@haskell.org> #12378: Not enough inlining happens with single-method type classes -------------------------------------+------------------------------------- Reporter: akio | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.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: | -------------------------------------+------------------------------------- Changes (by akio): * Attachment "test.hs" added. test case -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 11 07:03:05 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 11 Jul 2016 07:03:05 -0000 Subject: [GHC] #12379: WARN pragma gives warning `warning: [-Wdeprecations]' Message-ID: <045.155a5978502e79d25fe769eea3d3ec0b@haskell.org> #12379: WARN pragma gives warning `warning: [-Wdeprecations]' -------------------------------------+------------------------------------- Reporter: zilinc | Owner: Type: bug | Status: new Priority: low | Milestone: Component: Compiler | Version: 8.0.1 Keywords: | Operating System: Linux Architecture: x86_64 | Type of failure: Incorrect (amd64) | warning at compile-time Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- Example: {{{#!hs -- Warn.hs module Warn where __todo :: String -> a {-# WARNING __todo "TODO" #-} __todo msg = error $ "TODO: " ++ msg }}} {{{#!hs -- Main.hs {- OPTIONS_GHC -Wall #-} import Warn inc :: Int -> Int inc n | n >= 0 = n + 1 inc _ = __todo "what about negatives?" }}} When compile the files (or ghci), I get {{{ UseWarn.hs:9:9: warning: [-Wdeprecations] In the use of ‘__todo’ (imported from Warn): "TODO" }}} Should the flag be `-Wwarnings-deprecations`? And `-Wdeprecations` is not in the user guide, if it is a genuine flag. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 11 08:34:17 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 11 Jul 2016 08:34:17 -0000 Subject: [GHC] #10352: Properly link Haskell shared libs on ELF systems In-Reply-To: <045.f54c0b53e462b1ea305eb5f3c38d7688@haskell.org> References: <045.f54c0b53e462b1ea305eb5f3c38d7688@haskell.org> Message-ID: <060.ae6b3231d696ce7238ba9df3dc3e8cb3@haskell.org> #10352: Properly link Haskell shared libs on ELF systems -------------------------------------+------------------------------------- Reporter: duncan | Owner: Type: task | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.11 (Linking) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: 5987 Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by trommler): Just an idea: The RTS is split into two parts, a small stub library and the actual RTS library (respectively its flavours). The stub library checks for an RTS parameter or an environment variable or ... to determine the flavour of RTS desired. The stub library `dlopen`s the appropriate shared library with `RTLD_GLOBAL` scope, which makes all RTS symbols available to all shared libraries loaded after. The linking of the stub RTS results in dangling references which is fine for ELF shared libraries. Perhaps, the functionality of the stub library could also be integrated into hs_init(). In that case libraries depending on the RTS must not be linked against any flavour of the RTS resulting in dangling references. That is fine in ELF. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 11 09:10:35 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 11 Jul 2016 09:10:35 -0000 Subject: [GHC] #12376: Allow function definitions in record syntax In-Reply-To: <051.ff1dad08610f3c1f3808a2894d40fdae@haskell.org> References: <051.ff1dad08610f3c1f3808a2894d40fdae@haskell.org> Message-ID: <066.6d095257ac041c92f829f6410c7f5980@haskell.org> #12376: Allow function definitions in record syntax -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: 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: | -------------------------------------+------------------------------------- Comment (by simonpj): One more piece of syntactic sugar. I see no difficulty in principle. What about recursion? Currently record fields are in scope in the RHS, but only as record selectors, not as the function being defined. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 11 09:11:03 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 11 Jul 2016 09:11:03 -0000 Subject: [GHC] #12370: Implement LetUp in DmdAnal (or document why we do not do it) In-Reply-To: <046.4d0b4649e15ed41a4a32187881ac4332@haskell.org> References: <046.4d0b4649e15ed41a4a32187881ac4332@haskell.org> Message-ID: <061.86fccbaaeb407c49a2f3d0b53818c75f@haskell.org> #12370: Implement LetUp in DmdAnal (or document why we do not do it) -------------------------------------+------------------------------------- Reporter: nomeata | Owner: Type: task | Status: patch Priority: normal | Milestone: Component: Compiler | 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): Phab:D2395 Wiki Page: | -------------------------------------+------------------------------------- Changes (by nomeata): * status: new => patch * differential: => Phab:D2395 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 11 09:45:12 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 11 Jul 2016 09:45:12 -0000 Subject: [GHC] #3919: Or-patterns as GHC extension In-Reply-To: <051.27f4dc97a096cc6bd656d7691ce3afb5@haskell.org> References: <051.27f4dc97a096cc6bd656d7691ce3afb5@haskell.org> Message-ID: <066.22a5751c7c89c238ca6bdfc65b526b6a@haskell.org> #3919: Or-patterns as GHC extension -------------------------------------+------------------------------------- Reporter: BjornEdstrom | Owner: Type: feature request | Status: new Priority: normal | Milestone: ⊥ 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): Wiki Page: | -------------------------------------+------------------------------------- Changes (by mpickering): * cc: mpickering (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 11 09:54:24 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 11 Jul 2016 09:54:24 -0000 Subject: [GHC] #12357: Increasing maximum constraint tuple size significantly blows up compiler allocations In-Reply-To: <046.dd0f12e974ac3c5c9febd70397bf4138@haskell.org> References: <046.dd0f12e974ac3c5c9febd70397bf4138@haskell.org> Message-ID: <061.54680d94f66094e6b5e6cb45f813a60b@haskell.org> #12357: Increasing maximum constraint tuple size significantly blows up compiler allocations -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.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): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): See [https://phabricator.haskell.org/D2385#69455 Omer's comments] on the (now-closed) Phab patch. I'm responding here because Trac is a more durable medium than closed code reviews. I have not been paying proper attention to this ticket. But the solution embodied here (and now in HEAD) really isn't right. The new situation in `lookupOrigNameCache` is this: 1. Look up the `OccName` in fixed finite map, designed to catch tuples 2. If that fails, look up the (`Module`, `OccName`) pair in the original name cache. This is just a two-level finite map: first look up the `Module` then the `OccName`. So now, for every non-tuple, we do two lookups, in step 1 and step 2 resp. This is obviously bad. If we are going to have a finite map for tuples, just populate the original-name cache with tuples, and do step (2) alone. Even if tuples are treated specially somehow, as Omer says, it would be be far better to first spot that the `Module` is `GHC.Tuple` and only then do tuple-processing. But what we have now is (a) more complicated and (b) slower than this. For tuples, maybe it's ok to populate the cache with 62 tycons and 62 datacons. For for unboxed sums we'll have 62*62 data cons, which we might consider too many. It may be that a little hand-written parser, working directly on `ByteString` would be better. But regardless that should be a decision that affects only the code path when we reallydo have a tuple, not everything. Another option that we explored in the past was to have a special interface-file representation for these name-families (tuples and sums). Perhaps {{{ data IfaceType = ... | IfaceTuple Boxity Arity }}} meaning just an occurence of the naked `TyCon`. Now the string `GHC.Tuple.(,,,)` would never occur, so this entire question would not be relevant for interface file serialisation and deserialisation. (We'd still need that parser for Template Haskell.) I'm not sure why we abandoned that approach. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 11 11:09:40 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 11 Jul 2016 11:09:40 -0000 Subject: [GHC] #12380: ghc: panic! (the 'impossible' happened) Message-ID: <047.e34a54a22884f581cc455807c95f0c38@haskell.org> #12380: ghc: panic! (the 'impossible' happened) --------------------------------------+--------------------------------- Reporter: Hassan58 | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 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: --------------------------------------+--------------------------------- -- While building package yesod-auth-1.4.13.3 using: /Users/hassanshahin/.stack/setup-exe-cache/x86_64-osx/setup-Simple- Cabal-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/hassanshahin/my-project/.stack- work/logs/yesod-auth-1.4.13.3.log Configuring yesod-auth-1.4.13.3... Building yesod-auth-1.4.13.3... Preprocessing library yesod-auth-1.4.13.3... [ 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/g5/5wkx70392bs5gv_5tvvwbl180000gn/T/stack72472 /yesod-auth-1.4.13.3/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/g5/5wkx70392bs5gv_5tvvwbl180000gn/T/stack72472 /yesod-auth-1.4.13.3/Yesod/PasswordStore.hs:419:1: Warning: Defined but not used: ‘toStrict’ /private/var/folders/g5/5wkx70392bs5gv_5tvvwbl180000gn/T/stack72472 /yesod-auth-1.4.13.3/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/g5/5wkx70392bs5gv_5tvvwbl180000gn/T/stack72472 /yesod-auth-1.4.13.3/Yesod/Auth/Message.hs:23:1: Warning: The import of ‘mappend’ from module ‘Data.Monoid’ is redundant /private/var/folders/g5/5wkx70392bs5gv_5tvvwbl180000gn/T/stack72472 /yesod-auth-1.4.13.3/Yesod/Auth/Message.hs:698:1: Warning: Defined but not used: ‘croatianMessage’ /private/var/folders/g5/5wkx70392bs5gv_5tvvwbl180000gn/T/stack72472 /yesod-auth-1.4.13.3/Yesod/Auth/Message.hs:459:1: Warning: Pattern match(es) are overlapped In an equation for ‘finnishMessage’: finnishMessage Password = ... /private/var/folders/g5/5wkx70392bs5gv_5tvvwbl180000gn/T/stack72472 /yesod-auth-1.4.13.3/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/g5/5wkx70392bs5gv_5tvvwbl180000gn/T/ghc72516_0/libghc_21.dylib, 5): no suitable image found. Did find: /var/folders/g5/5wkx70392bs5gv_5tvvwbl180000gn/T/ghc72516_0/libghc_21.dylib: malformed mach-o: load commands size (36488) > 32768 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 Jul 11 11:11:23 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 11 Jul 2016 11:11:23 -0000 Subject: [GHC] #12380: ghc: panic! (the 'impossible' happened) In-Reply-To: <047.e34a54a22884f581cc455807c95f0c38@haskell.org> References: <047.e34a54a22884f581cc455807c95f0c38@haskell.org> Message-ID: <062.064348bc2f0dc10b7675e669e5bbe527@haskell.org> #12380: ghc: panic! (the 'impossible' happened) ---------------------------------+-------------------------------------- Reporter: Hassan58 | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 Resolution: | 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: | ---------------------------------+-------------------------------------- Changes (by Hassan58): * Attachment "yesod-auth-1.4.13.3.log" added. Log file -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 11 11:45:18 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 11 Jul 2016 11:45:18 -0000 Subject: [GHC] #10886: Remove the magic from `Any` In-Reply-To: <047.f678cbb73069d1c6ee1f63fe7d449257@haskell.org> References: <047.f678cbb73069d1c6ee1f63fe7d449257@haskell.org> Message-ID: <062.0172203b50cc01d41a7e95552eb27612@haskell.org> #10886: Remove the magic from `Any` -------------------------------------+------------------------------------- Reporter: goldfire | Owner: goldfire Type: task | Status: closed Priority: normal | Milestone: 8.2.1 Component: Compiler | Version: 7.10.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:D2049 Wiki Page: | -------------------------------------+------------------------------------- Comment (by thomie): This should probably be mentioned in release notes and migration guide. This breaks for example the `constraints` package (it uses `Any` from `Prim`). These kind of little breakages are annoying, and seem so unnecessary. Can we do something about it? A suggestion: * Rename `GHC.Prim` to something else, and make `GHC.Prim` a backward compatible module that exports `GHC.Exts` (including `Any` and `Constraints` for example). This seems less work than replacing `GHC.Prim` to `GHC.Exts` across hackage. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 11 12:21:42 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 11 Jul 2016 12:21:42 -0000 Subject: [GHC] #10886: Remove the magic from `Any` In-Reply-To: <047.f678cbb73069d1c6ee1f63fe7d449257@haskell.org> References: <047.f678cbb73069d1c6ee1f63fe7d449257@haskell.org> Message-ID: <062.35d6b805c01e44d673e74787701bf55b@haskell.org> #10886: Remove the magic from `Any` -------------------------------------+------------------------------------- Reporter: goldfire | Owner: goldfire Type: task | Status: closed Priority: normal | Milestone: 8.2.1 Component: Compiler | Version: 7.10.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:D2049 Wiki Page: | -------------------------------------+------------------------------------- Comment (by goldfire): While of course it can be mentioned in the migration guide on the wiki, I specifically chose not to mention this in the release notes. (Actually, looking through the history on this ticket, Ben did the heavy lifting. Thanks, Ben. But there were other definitions that I moved out of `GHC.Prim` for 8.0.) The reason is this sentence from the module documentation on `GHC.Prim`: "Use GHC.Exts from the base package instead of importing this module directly." I thus assumed that `GHC.Prim` was entirely an internal implementation artifact and did not think a change notification was necessary. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 11 13:49:20 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 11 Jul 2016 13:49:20 -0000 Subject: [GHC] #10886: Remove the magic from `Any` In-Reply-To: <047.f678cbb73069d1c6ee1f63fe7d449257@haskell.org> References: <047.f678cbb73069d1c6ee1f63fe7d449257@haskell.org> Message-ID: <062.80855f87fb6c11fe984e38388a0ac8dd@haskell.org> #10886: Remove the magic from `Any` -------------------------------------+------------------------------------- Reporter: goldfire | Owner: goldfire Type: task | Status: closed Priority: normal | Milestone: 8.2.1 Component: Compiler | Version: 7.10.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:D2049 Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): > Rename `GHC.Prim` to something else, and make `GHC.Prim` a backward compatible module that exports `GHC.Exts` (including `Any` and `Constraints` for example). As Richard mentioned, this is actually backwards. Currently users are advised to use `GHC.Exts`, which should re-export anything of use provided by `GHC.Prim`. Unfortunately, it seems that this message perhaps isn't as widely known as it should be. I'm not sure how else to convey it, however. > I thus assumed that `GHC.Prim` was entirely an internal implementation artifact Indeed it is. In fact, it is quite a magical module (e.g. it has no object code; the source Haskell module generated by `mkPrimOps` is actually merely for consumption by Haddock), so renaming it as thomie suggests would require a fair number of changes in the compiler. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 11 13:55:28 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 11 Jul 2016 13:55:28 -0000 Subject: [GHC] #12357: Increasing maximum constraint tuple size significantly blows up compiler allocations In-Reply-To: <046.dd0f12e974ac3c5c9febd70397bf4138@haskell.org> References: <046.dd0f12e974ac3c5c9febd70397bf4138@haskell.org> Message-ID: <061.c03c3244912c0f45130e40546823b633@haskell.org> #12357: Increasing maximum constraint tuple size significantly blows up compiler allocations -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.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): Wiki Page: | -------------------------------------+------------------------------------- Changes (by osa1): * cc: osa1 (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 11 13:56:22 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 11 Jul 2016 13:56:22 -0000 Subject: [GHC] #12367: Commit adding instances to GHC.Generics regression compiler performance In-Reply-To: <046.87a5f8a842934b4554eedf79fb6bebbc@haskell.org> References: <046.87a5f8a842934b4554eedf79fb6bebbc@haskell.org> Message-ID: <061.022bf6beb5e3658c087929e1e2ca2cce@haskell.org> #12367: Commit adding instances to GHC.Generics regression compiler performance -------------------------------------+------------------------------------- Reporter: bgamari | Owner: bgamari Type: bug | Status: new Priority: normal | Milestone: 8.0.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: | -------------------------------------+------------------------------------- Comment (by bgamari): To characterize this further I chose a representative module from nofib (the `Psfuns` module of the `reptile` test) and compiled it with 6319a8cf79cc1f1e25220113149ab48e5083321b (the parent of the change) and 673efccb3b348e9daf23d9e65460691bbea8586e built with ticky enabled. The largest changes are summarized below. ||= Change =||= alloc A =||= alloc B =||= name =|| || +2898040.0 || 13460520 || 16358560 || `$wa5 (ghc-8.1:Encoding)` || || +2247360.0 || 6593640 || 8841000 || ` (ghc-8.1:Unique.mkUnique)` || || +1976688.0 || 8486408 || 10463096 || `a4 (ghc-8.1:IOEnv)` || || +1734288.0 || 5736672 || 7470960 || ` (ghc-8.1:FastString.uniq)` || || +1632784.0 || 5415504 || 7048288 || `$cgetUnique2 (ghc-8.1:Unique)` || || +1258016.0 || 3014864 || 4272880 || ` (ghc-8.1:Binary.getByte1)` || || +1229472.0 || 4354032 || 5583504 || `$ccompare1 (ghc-8.1:Module)` || || +1210656.0 || 3661152 || 4871808 || `$ccompare (ghc-8.1:Module)` || || +1083360.0 || 2529840 || 3613200 || `$cget6 (ghc-8.1:IfaceType)` || || +994560.0 || 2327440 || 3322000 || `$wa1 (ghc-8.1:BinIface.)` || || +960600.0 || 2005200 || 2965800 || `$cget5 (ghc-8.1:IfaceType)` || || +946824.0 || 2020656 || 2967480 || `$wa3 (ghc-8.1:BinIface)` || || +558992.0 || 1389872 || 1948864 || `$wa8 (ghc-8.1:Binary.)` || || +558200.0 || 1193720 || 1751920 || `$cget1 (ghc-8.1:IfaceType)` || || +551320.0 || 1149720 || 1701040 || `$cget2 (ghc-8.1:IfaceType)` || || +473088.0 || 1268960 || 1742048 || ` (ghc-8.1:TysWiredIn.isBuiltInOcc_maybe)` || || +318136.0 || 1234352 || 1552488 || `a5 (ghc-8.1:IOEnv)` || || +305280.0 || 4939520 || 5244800 || ` (ghc-8.1:UniqFM.lookupUFM)` || || +297216.0 || 691920 || 989136 || ` (ghc-8.1:UniqFM.lookupUFM_Directly)` || || +286200.0 || 889680 || 1175880 || `$wa17 (ghc-8.1:Binary.)` || || +253952.0 || 560000 || 813952 || `a18 (ghc-8.1:BinIface)` || || +217992.0 || 1167832 || 1385824 || `$wa (ghc-8.1:FastString.)` || || +187792.0 || 595672 || 783464 || ` (ghc-8.1:IfaceEnv.lookupOrig)` || || +173720.0 || 566160 || 739880 || ` (ghc-8.1:FastString.unpackFS)` || || +173504.0 || 397760 || 571264 || `$wa11 (ghc-8.1:Binary.)` || || +170560.0 || 694272 || 864832 || `a (ghc-8.1:IOEnv)` || || +148992.0 || 3369216 || 3518208 || `a23 (ghc-8.1:UniqFM)` || || +137376.0 || 456528 || 593904 || ` (ghc-8.1:Unique.mkVarOccUnique)` || || +134320.0 || 2260808 || 2395128 || ` (ghc-8.1:DynFlags.dopt)` || || +133448.0 || 413840 || 547288 || `$wxs (ghc-8.1:Binary)` || || +117936.0 || 363664 || 481600 || ` (ghc-8.1:IfaceEnv.extendNameCache)` || || +117544.0 || 401520 || 519064 || ` (ghc-8.1:Name.mkExternalName)` || || +114240.0 || 265632 || 379872 || `$fBinary(,)`1 (ghc-8.1:Binary.) || || +110992.0 || 243824 || 354816 || `$wxs (ghc-8.1:BinIface)` || || +108480.0 || 222640 || 331120 || `$cget (ghc-8.1:TyCoRep)` || || +108480.0 || 222640 || 331120 || `$cget4 (ghc-8.1:IfaceType)` || || +106920.0 || 473448 || 580368 || `$wa83 (ghc-8.1:Binary)` || || +105888.0 || 229248 || 335136 || ` (ghc-8.1:TcRnMonad.forkM)` || || +104232.0 || 340752 || 444984 || `$wa2 (ghc-8.1:Encoding.)` || || +103200.0 || 385296 || 488496 || ` (ghc-8.1:UniqSupply.takeUniqFromSupply)` || || +98576.0 || 263312 || 361888 || `$wa6 (ghc-8.1:Binary.)` || || +93600.0 || 197040 || 290640 || `$cget1 (ghc-8.1:OccName)` || -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 11 14:20:15 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 11 Jul 2016 14:20:15 -0000 Subject: [GHC] #12367: Commit adding instances to GHC.Generics regression compiler performance In-Reply-To: <046.87a5f8a842934b4554eedf79fb6bebbc@haskell.org> References: <046.87a5f8a842934b4554eedf79fb6bebbc@haskell.org> Message-ID: <061.005a9db65f16b83f2286c511e24f8d24@haskell.org> #12367: Commit adding instances to GHC.Generics regression compiler performance -------------------------------------+------------------------------------- Reporter: bgamari | Owner: bgamari Type: bug | Status: new Priority: normal | Milestone: 8.0.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: | -------------------------------------+------------------------------------- Comment (by bgamari): It turns out that the problem is actually a fair bit worse than described above. While `Foldable` imports `GHC.Generics` in order to provide instances for types in the latter (which should be fairly easy to fix with some reorganization), the other modules import `GHC.Generics merely to derive `Generic` instances for types they themselves define. One example of this is `Data.Monoid`, which defines a number of `newtype`s resembling, {{{#!hs newtype All = All { getAll :: Bool } deriving (Eq, Ord, Read, Show, Bounded, Generic) }}} It seems to me like we may want to consider moving the data types defined in `GHC.Generics` to a new `GHC.Generic.Internal` module. They could then be re-exported in `GHC.Generics`, which could also derive instances for these types. This would also allow us to move the `Foldable` instances for the generics types to `GHC.Generics`, since the latter could likely import `Data.Foldable` without fear of cycles. Really, though, this arguably leaves a large portion of the problem unsolved: users who use `GHC.Generics` (which is increasingly popular) still need to pay the full cost of importing it. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 11 14:22:22 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 11 Jul 2016 14:22:22 -0000 Subject: [GHC] #12367: Commit adding instances to GHC.Generics regression compiler performance In-Reply-To: <046.87a5f8a842934b4554eedf79fb6bebbc@haskell.org> References: <046.87a5f8a842934b4554eedf79fb6bebbc@haskell.org> Message-ID: <061.8c56fbe2f2ba7e65d87a56c25d427a0f@haskell.org> #12367: Commit adding instances to GHC.Generics regression compiler performance -------------------------------------+------------------------------------- Reporter: bgamari | Owner: bgamari Type: bug | Status: new Priority: normal | Milestone: 8.0.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): * cc: RyanGlScott (added) Comment: Ccing RyanGlScott, who authored 673efccb3b348e9daf23d9e65460691bbea8586e. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 11 14:51:24 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 11 Jul 2016 14:51:24 -0000 Subject: [GHC] #12367: Commit adding instances to GHC.Generics regression compiler performance In-Reply-To: <046.87a5f8a842934b4554eedf79fb6bebbc@haskell.org> References: <046.87a5f8a842934b4554eedf79fb6bebbc@haskell.org> Message-ID: <061.c8c2c61a7e2ef4b147afc1e5e670fa00@haskell.org> #12367: Commit adding instances to GHC.Generics regression compiler performance -------------------------------------+------------------------------------- Reporter: bgamari | Owner: bgamari Type: bug | Status: new Priority: normal | Milestone: 8.0.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: | -------------------------------------+------------------------------------- Comment (by bgamari): I should note that the problem of adding instances to core libraries degrading compiler performance is a rather general theme. It can also be found in 4e6bcc2c8134f9c1ba7d715b3206130f23c529fb, which adds a number of instances to `Data.Monoid` and regresses compiler allocations by 5 to 10%. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 11 15:28:28 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 11 Jul 2016 15:28:28 -0000 Subject: [GHC] #12380: ghc: panic! (the 'impossible' happened) In-Reply-To: <047.e34a54a22884f581cc455807c95f0c38@haskell.org> References: <047.e34a54a22884f581cc455807c95f0c38@haskell.org> Message-ID: <062.d026b94205230f174c18b374f404b944@haskell.org> #12380: ghc: panic! (the 'impossible' happened) ---------------------------------+-------------------------------------- Reporter: Hassan58 | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 Resolution: | 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: | ---------------------------------+-------------------------------------- Description changed by simonpj: @@ -1,1 +1,2 @@ - -- While building package yesod-auth-1.4.13.3 using: + While building package yesod-auth-1.4.13.3 using: + {{{ @@ -70,0 +71,1 @@ + }}} New description: While building package yesod-auth-1.4.13.3 using: {{{ /Users/hassanshahin/.stack/setup-exe-cache/x86_64-osx/setup-Simple- Cabal-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/hassanshahin/my-project/.stack- work/logs/yesod-auth-1.4.13.3.log Configuring yesod-auth-1.4.13.3... Building yesod-auth-1.4.13.3... Preprocessing library yesod-auth-1.4.13.3... [ 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/g5/5wkx70392bs5gv_5tvvwbl180000gn/T/stack72472 /yesod-auth-1.4.13.3/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/g5/5wkx70392bs5gv_5tvvwbl180000gn/T/stack72472 /yesod-auth-1.4.13.3/Yesod/PasswordStore.hs:419:1: Warning: Defined but not used: ‘toStrict’ /private/var/folders/g5/5wkx70392bs5gv_5tvvwbl180000gn/T/stack72472 /yesod-auth-1.4.13.3/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/g5/5wkx70392bs5gv_5tvvwbl180000gn/T/stack72472 /yesod-auth-1.4.13.3/Yesod/Auth/Message.hs:23:1: Warning: The import of ‘mappend’ from module ‘Data.Monoid’ is redundant /private/var/folders/g5/5wkx70392bs5gv_5tvvwbl180000gn/T/stack72472 /yesod-auth-1.4.13.3/Yesod/Auth/Message.hs:698:1: Warning: Defined but not used: ‘croatianMessage’ /private/var/folders/g5/5wkx70392bs5gv_5tvvwbl180000gn/T/stack72472 /yesod-auth-1.4.13.3/Yesod/Auth/Message.hs:459:1: Warning: Pattern match(es) are overlapped In an equation for ‘finnishMessage’: finnishMessage Password = ... /private/var/folders/g5/5wkx70392bs5gv_5tvvwbl180000gn/T/stack72472 /yesod-auth-1.4.13.3/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/g5/5wkx70392bs5gv_5tvvwbl180000gn/T/ghc72516_0/libghc_21.dylib, 5): no suitable image found. Did find: /var/folders/g5/5wkx70392bs5gv_5tvvwbl180000gn/T/ghc72516_0/libghc_21.dylib: malformed mach-o: load commands size (36488) > 32768 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 Jul 11 16:35:08 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 11 Jul 2016 16:35:08 -0000 Subject: [GHC] #12367: Commit adding instances to GHC.Generics regression compiler performance In-Reply-To: <046.87a5f8a842934b4554eedf79fb6bebbc@haskell.org> References: <046.87a5f8a842934b4554eedf79fb6bebbc@haskell.org> Message-ID: <061.a754d6948d16811cc52a7be5c5e501c8@haskell.org> #12367: Commit adding instances to GHC.Generics regression compiler performance -------------------------------------+------------------------------------- Reporter: bgamari | Owner: bgamari Type: bug | Status: new Priority: normal | Milestone: 8.0.2 Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Generics 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 RyanGlScott): * keywords: => Generics -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 11 16:52:14 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 11 Jul 2016 16:52:14 -0000 Subject: [GHC] #12381: Type family not reduced Message-ID: <046.0dea1b11f4af8f3cac37c083d6847cd7@haskell.org> #12381: Type family not reduced -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: bug | Status: new Priority: normal | Milestone: 8.0.2 Component: Compiler | Version: 8.0.1 (Type checker) | 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: -------------------------------------+------------------------------------- Andres pointed out that the following fails to compile with GHC 8.0.1 but succeeds with `master` (f53d761df9762232b54ec57a950d301011cd21f8), {{{#!hs {-# LANGUAGE TypeInType, TypeFamilies #-} module Kinds where import GHC.Types type family G (a :: Type) :: Type type instance G Int = Bool type family F (a :: Type) :: G a type instance F Int = True }}} Error: {{{ Hi.hs:10:23: error: • Expected kind ‘G Int’, but ‘'True’ has kind ‘Bool’ • In the type ‘True’ In the type instance declaration for ‘F’ }}} We should figure out what fixed this so it can hopefully be merged for 8.0.2. I initially suspected the patch cited in #12175 but sadly this doesn't seem to be the case. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 11 16:52:23 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 11 Jul 2016 16:52:23 -0000 Subject: [GHC] #12381: Type family not reduced In-Reply-To: <046.0dea1b11f4af8f3cac37c083d6847cd7@haskell.org> References: <046.0dea1b11f4af8f3cac37c083d6847cd7@haskell.org> Message-ID: <061.3a807aad06b428a970898a3a6a418116@haskell.org> #12381: Type family not reduced -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: bug | Status: merge Priority: normal | Milestone: 8.0.2 Component: Compiler (Type | Version: 8.0.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): * status: new => merge -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 11 17:41:31 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 11 Jul 2016 17:41:31 -0000 Subject: [GHC] #9123: Need for higher kinded roles In-Reply-To: <046.743e1f5edf878b0ae2d2d6b5081e6a33@haskell.org> References: <046.743e1f5edf878b0ae2d2d6b5081e6a33@haskell.org> Message-ID: <061.a14da3ed45278556af970627c277328a@haskell.org> #9123: Need for higher kinded roles -------------------------------------+------------------------------------- Reporter: simonpj | Owner: goldfire Type: bug | 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: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * cc: RyanGlScott (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 11 17:46:56 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 11 Jul 2016 17:46:56 -0000 Subject: [GHC] #2256: Incompleteness of type inference: must quantify over implication constraints In-Reply-To: <046.2c6c7c4440a32ff5fbe5ad1f48bf6276@haskell.org> References: <046.2c6c7c4440a32ff5fbe5ad1f48bf6276@haskell.org> Message-ID: <061.69ef45f309a0615152f38eccb9a60678@haskell.org> #2256: Incompleteness of type inference: must quantify over implication constraints -------------------------------------+------------------------------------- Reporter: simonpj | Owner: simonpj Type: bug | Status: new Priority: lowest | Milestone: Component: Compiler (Type | Version: 6.8.2 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 Mon Jul 11 17:58:38 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 11 Jul 2016 17:58:38 -0000 Subject: [GHC] #12227: regression: out of memory with -O2 -ddump-hi on a complex INLINE function In-Reply-To: <046.5eb6cdc259c89a5a386fca350cf30507@haskell.org> References: <046.5eb6cdc259c89a5a386fca350cf30507@haskell.org> Message-ID: <061.3865d6a1bfd11795f427d58777f8da50@haskell.org> #12227: regression: out of memory with -O2 -ddump-hi on a complex INLINE function -------------------------------------+------------------------------------- Reporter: j6carey | Owner: Type: bug | Status: patch Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 (CodeGen) | Resolution: | Keywords: Operating System: Linux | Architecture: x86_64 | (amd64) Type of failure: None/Unknown | Test Case: | perf/compiler/T12227 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2397 Wiki Page: | -------------------------------------+------------------------------------- Changes (by thomie): * status: new => patch * testcase: => perf/compiler/T12227 * differential: => Phab:D2397 Comment: The [http://git.haskell.org/packages/pretty.git/commit/bbe9270c5f849a5bb74c9166a5f4202cfb0dba22 fix] for that `pretty` issue also fixes this bug. I don't understand why exactly, but I'm happy to apply it. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 11 18:15:26 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 11 Jul 2016 18:15:26 -0000 Subject: [GHC] #10352: Properly link Haskell shared libs on ELF systems In-Reply-To: <045.f54c0b53e462b1ea305eb5f3c38d7688@haskell.org> References: <045.f54c0b53e462b1ea305eb5f3c38d7688@haskell.org> Message-ID: <060.fddbb20ed039982d656095f1a9d5dfd6@haskell.org> #10352: Properly link Haskell shared libs on ELF systems -------------------------------------+------------------------------------- Reporter: duncan | Owner: Type: task | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.11 (Linking) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: 5987 Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Phyx-): Hmm, but what would the advantages of this be over the proposed solution though? At least for Windows the implementation would be a bit more complicated... -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 11 18:29:28 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 11 Jul 2016 18:29:28 -0000 Subject: [GHC] #12381: Type family not reduced In-Reply-To: <046.0dea1b11f4af8f3cac37c083d6847cd7@haskell.org> References: <046.0dea1b11f4af8f3cac37c083d6847cd7@haskell.org> Message-ID: <061.a6f6f49dedd825a47a99610c747d774a@haskell.org> #12381: Type family not reduced -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: bug | Status: merge Priority: normal | Milestone: 8.0.2 Component: Compiler (Type | Version: 8.0.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: | -------------------------------------+------------------------------------- Comment (by alexvieth): > We should figure out what fixed this I believe it's #11348. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 11 19:03:45 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 11 Jul 2016 19:03:45 -0000 Subject: [GHC] #10886: Remove the magic from `Any` In-Reply-To: <047.f678cbb73069d1c6ee1f63fe7d449257@haskell.org> References: <047.f678cbb73069d1c6ee1f63fe7d449257@haskell.org> Message-ID: <062.970394a561d14924a42193e166a26a93@haskell.org> #10886: Remove the magic from `Any` -------------------------------------+------------------------------------- Reporter: goldfire | Owner: goldfire Type: task | Status: closed Priority: normal | Milestone: 8.2.1 Component: Compiler | Version: 7.10.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:D2049 Wiki Page: | -------------------------------------+------------------------------------- Comment (by thomie): It doesn't matter that there is a small comment in the documentation that says to use `GHC.Exts` instead. `GHC.Prim` is out there, visible on hackage, and people are using it. There are ~375 modules importing `GHC.Prim` across 163 hackage packages. With GHC 8.0 and 8.2 some of those packages will be broken. What about 8.4? Breaking user code is bad, especially if there is zero benefit to users, and just causes busywork for users and maintainers. I run into these problems all the time when trying to reproduce bug reports with HEAD, and it's really quite annoying. > renaming it [..] would require a fair number of changes in the compiler I don't understand. But I guess there are a million more urgent GHC problems to work on, so I guess I should let it rest. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 11 19:36:28 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 11 Jul 2016 19:36:28 -0000 Subject: [GHC] #12227: regression: out of memory with -O2 -ddump-hi on a complex INLINE function In-Reply-To: <046.5eb6cdc259c89a5a386fca350cf30507@haskell.org> References: <046.5eb6cdc259c89a5a386fca350cf30507@haskell.org> Message-ID: <061.cb0a39df147855cd601c68e522de64e8@haskell.org> #12227: regression: out of memory with -O2 -ddump-hi on a complex INLINE function -------------------------------------+------------------------------------- Reporter: j6carey | Owner: Type: bug | Status: patch Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 (CodeGen) | Resolution: | Keywords: Operating System: Linux | Architecture: x86_64 | (amd64) Type of failure: None/Unknown | Test Case: | perf/compiler/T12227 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2397 Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): Well caught, thomie! -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 11 19:50:47 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 11 Jul 2016 19:50:47 -0000 Subject: [GHC] #10886: Remove the magic from `Any` In-Reply-To: <047.f678cbb73069d1c6ee1f63fe7d449257@haskell.org> References: <047.f678cbb73069d1c6ee1f63fe7d449257@haskell.org> Message-ID: <062.0374105a41b61bd3f786aa1881fefc05@haskell.org> #10886: Remove the magic from `Any` -------------------------------------+------------------------------------- Reporter: goldfire | Owner: goldfire Type: task | Status: closed Priority: normal | Milestone: 8.2.1 Component: Compiler | Version: 7.10.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:D2049 Wiki Page: | -------------------------------------+------------------------------------- Comment (by ezyang): The widespread use of GHC.Prim is primarily an accident induced by documentation: https://hackage.haskell.org/package/base-4.9.0.0/docs/GHC- Exts.html does not list all of the GHC.Prim functions; instead there's just a little "module GHC.Prim" deep inside. So if I'm looking up a function, the only Haddock page it is going to be on is GHC.Prim, and then of course I'm going to import GHC.Prim (if I am not paying close attention). So I guess what could be done is to change what the magical module is called, turn GHC.Prim into a real module, DON'T expose it, and this time correctly configure Haddock to inline the description so that whatever your real module is called never gets exposed. A bit of faffing about but probably not fundamentally hard. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 11 20:39:41 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 11 Jul 2016 20:39:41 -0000 Subject: [GHC] #9517: hp2ps generates invalid postscript file In-Reply-To: <045.a830b70a270e850cd0392ed106ef100c@haskell.org> References: <045.a830b70a270e850cd0392ed106ef100c@haskell.org> Message-ID: <060.96550d0ec599f517550c77c65ea5627f@haskell.org> #9517: hp2ps generates invalid postscript file -------------------------------------+------------------------------------- Reporter: JamesM | Owner: Type: bug | Status: patch Priority: normal | Milestone: Component: Profiling | Version: 7.10.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Other | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2398 Wiki Page: | -------------------------------------+------------------------------------- Changes (by thomie): * status: new => patch * differential: => Phab:D2398 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 11 20:41:47 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 11 Jul 2016 20:41:47 -0000 Subject: [GHC] #12381: Type family not reduced In-Reply-To: <046.0dea1b11f4af8f3cac37c083d6847cd7@haskell.org> References: <046.0dea1b11f4af8f3cac37c083d6847cd7@haskell.org> Message-ID: <061.e7a0b65dd96c61de237a388c58716d6b@haskell.org> #12381: Type family not reduced -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: bug | Status: merge Priority: normal | Milestone: 8.0.2 Component: Compiler (Type | Version: 8.0.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: | -------------------------------------+------------------------------------- Comment (by simonpj): Let's add this as a regression test though. (Redundant perhaps, but still.) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 11 20:52:34 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 11 Jul 2016 20:52:34 -0000 Subject: [GHC] #10886: Remove the magic from `Any` In-Reply-To: <047.f678cbb73069d1c6ee1f63fe7d449257@haskell.org> References: <047.f678cbb73069d1c6ee1f63fe7d449257@haskell.org> Message-ID: <062.2c481e85698b117b0b2db779cd9c83b6@haskell.org> #10886: Remove the magic from `Any` -------------------------------------+------------------------------------- Reporter: goldfire | Owner: goldfire Type: task | Status: closed Priority: normal | Milestone: 8.2.1 Component: Compiler | Version: 7.10.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:D2049 Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): Replying to [comment:12 ezyang]: > The widespread use of GHC.Prim is primarily an accident induced by documentation: https://hackage.haskell.org/package/base-4.9.0.0/docs/GHC- Exts.html does not list all of the GHC.Prim functions; instead there's just a little "module GHC.Prim" deep inside. So if I'm looking up a function, the only Haddock page it is going to be on is GHC.Prim, and then of course I'm going to import GHC.Prim (if I am not paying close attention). Indeed, our intent was that people should import `GHC.Exts` precisely to insulate them from the vaguaries of which module actually defines the thing. While that horse seems to have well and truly bolted, I wonder whether we could fix Haddock (or something) for the future, explain the intent, and encourage library authors to future-proof their code by updating their imports? Simon -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 11 21:13:53 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 11 Jul 2016 21:13:53 -0000 Subject: [GHC] #12168: panic! (the 'impossible' happened) with gi-gtk 3.0.4 In-Reply-To: <045.c1a720f41087b515211a480bde1e0805@haskell.org> References: <045.c1a720f41087b515211a480bde1e0805@haskell.org> Message-ID: <060.2c7cf43f11af4ca5be2211c2ef3384a9@haskell.org> #12168: panic! (the 'impossible' happened) with gi-gtk 3.0.4 -------------------------------------+------------------------------------- Reporter: drb226 | Owner: 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 drb226): I've created a persistent tagged docker image that can reproduce this issue. (It isn't the exact same image as before, but very similar.) {{{ $ docker pull danburton/stackage-build-server:2016-07-11 2016-07-11: Pulling from danburton/stackage-build-server Digest: sha256:1de56d2d293eeb3234cc9eadea06e0a9ef154052281905252442c520b1123f45 Status: Image is up to date for danburton/stackage-build-server:2016-07-11 }}} You can follow the docker-based repro instructions above, replacing {{{snoyberg/stackage:nightly}}} with {{{danburton/stackage-build- server:2016-07-11}}}, and you should get the same result. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 11 21:47:47 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 11 Jul 2016 21:47:47 -0000 Subject: [GHC] #10886: Remove the magic from `Any` In-Reply-To: <047.f678cbb73069d1c6ee1f63fe7d449257@haskell.org> References: <047.f678cbb73069d1c6ee1f63fe7d449257@haskell.org> Message-ID: <062.647a544b5232e80858bd2b2f0b655868@haskell.org> #10886: Remove the magic from `Any` -------------------------------------+------------------------------------- Reporter: goldfire | Owner: goldfire Type: task | Status: closed Priority: normal | Milestone: 8.2.1 Component: Compiler | Version: 7.10.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:D2049 Wiki Page: | -------------------------------------+------------------------------------- Comment (by ezyang): According to https://www.haskell.org/haddock/doc/html/ch03s04.html Haddock will only inline the documentation if the module is not completely reexported, or the module being reexported is marked with the hidden attribute. So Haddock DOES support inlining the documentation here; it's a matter of changing the default. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 11 22:59:46 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 11 Jul 2016 22:59:46 -0000 Subject: [GHC] #12177: Relevant bindings includes shadowed bindings In-Reply-To: <045.0e76a562090c9d87371f445f74b8515d@haskell.org> References: <045.0e76a562090c9d87371f445f74b8515d@haskell.org> Message-ID: <060.70718e6ba65824ed70363843f340e2fc@haskell.org> #12177: Relevant bindings includes shadowed bindings -------------------------------------+------------------------------------- Reporter: ezyang | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.1 checker) | 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 sgillespie): Using the above as an example, I presume the output should look like: {{{ :1:13: error: • Found hole: _ :: t2 Where: ‘t2’ is a rigid type variable bound by the inferred type of it :: t -> t1 -> t2 at :1:1 • In the expression: _ In the expression: \ x -> _ In the expression: \ x -> \ x -> _ • Relevant bindings include x :: t1 (bound at :1:8) it :: t -> t1 -> t2 (bound at :1:1) }}} Fare presumption? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 12 00:44:01 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 12 Jul 2016 00:44:01 -0000 Subject: [GHC] #2256: Incompleteness of type inference: must quantify over implication constraints In-Reply-To: <046.2c6c7c4440a32ff5fbe5ad1f48bf6276@haskell.org> References: <046.2c6c7c4440a32ff5fbe5ad1f48bf6276@haskell.org> Message-ID: <061.a4d82bdebb2e9ae06786d24e5d967d8a@haskell.org> #2256: Incompleteness of type inference: must quantify over implication constraints -------------------------------------+------------------------------------- Reporter: simonpj | Owner: simonpj Type: bug | Status: new Priority: lowest | Milestone: Component: Compiler (Type | Version: 6.8.2 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: | -------------------------------------+------------------------------------- Comment (by Iceland_jack): From [http://arxiv.org/pdf/1511.09394v1.pdf Proof Relevant Corecursive Resolution], I will copy the relevant text: > Derivable type classes.::: > > Hinze and Peyton Jones wanted to use an instance of the form > > {{{#!hs > instance (Binary a, Binary (f (GRose f a))) => Binary (GRose f a) > }}} > > but discovered that it causes resolution to diverge. They suggested the following as a replacement: > > {{{#!hs > instance (Binary a, ∀b. Binary b => Binary (f b)) => Binary (GRose f a) > }}} > > Unfortunately, Haskell does not support instances with ''polymorphic higher-order instance contexts''. Nevertheless, allowing such implication constraints would greatly increase the expressivity of corecursive resolution. In the terminology of our paper, it amounts to extending Horn formulas to intuitionistic formulas. Working with intuitionistic formulas would require a certain amount of searching, as the non-overlapping condition for Horn formulas is not enough to ensure uniqueness of the evidence. For example, consider the following axioms: > > {{{ > κ₁ : (A ⇒ B x) ⇒ D (S x) > ĸ₂ : A, D x ⇒ B (S x) > κ₃ : ⇒ D Z > }}} > We have two distinct proof terms for `D (S (S (S (S Z)))))`: > > {{{ > κ₁ (λα₁. ĸ₂ α₁ (ĸ₁ (λα₂. ĸ₂ α₁ ĸ₃)) > κ₁ (λα₁. ĸ₂ α₁ (ĸ₁ (λα₂. ĸ₂ α₂ ĸ₃)) > }}} > > This is undesirable from the perspective of generating evidence for type class. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 12 01:13:37 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 12 Jul 2016 01:13:37 -0000 Subject: [GHC] #393: functions without implementations In-Reply-To: <047.8e9c859b4db83c0d687094f53af0d886@haskell.org> References: <047.8e9c859b4db83c0d687094f53af0d886@haskell.org> Message-ID: <062.3e1daa9bc05d16779576d452c9db4eae@haskell.org> #393: functions without implementations -------------------------------------+------------------------------------- Reporter: c_maeder | Owner: Type: feature request | Status: closed Priority: normal | Milestone: ⊥ Component: Compiler (Type | Version: None checker) | Resolution: wontfix | 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): Useful when inferring types in GHCi. (ticket:2256#comment:25) I want to be able to write {{{ >>> data A; data B a; data D a; data S a; data Z >>> k1 :: (A -> B x) -> D (S x) >>> k2 :: A -> D x -> B (S x) >>> k3 :: D Z }}} {{{ >>> :t k1 (\a1 -> k2 a1 (k1 (\a2 -> k2 a1 k3))) k1 (\a1 -> k2 a1 (k1 (\a2 -> k2 a1 k3))) :: D (S (S (S (S Z)))) >>> :t k1 (\a1 -> k2 a1 (k1 (\a2 -> k2 a2 k3))) k1 (\a1 -> k2 a1 (k1 (\a2 -> k2 a2 k3))) :: D (S (S (S (S Z)))) }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 12 07:09:50 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 12 Jul 2016 07:09:50 -0000 Subject: [GHC] #12177: Relevant bindings includes shadowed bindings In-Reply-To: <045.0e76a562090c9d87371f445f74b8515d@haskell.org> References: <045.0e76a562090c9d87371f445f74b8515d@haskell.org> Message-ID: <060.adf82c0185c73767f53208c8aea3bffa@haskell.org> #12177: Relevant bindings includes shadowed bindings -------------------------------------+------------------------------------- Reporter: ezyang | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.1 checker) | 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): Good point. Can't be hard; we have a lexical environment to hand to check against. Anyone want to have a go? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 12 07:44:09 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 12 Jul 2016 07:44:09 -0000 Subject: [GHC] #10352: Properly link Haskell shared libs on ELF systems In-Reply-To: <045.f54c0b53e462b1ea305eb5f3c38d7688@haskell.org> References: <045.f54c0b53e462b1ea305eb5f3c38d7688@haskell.org> Message-ID: <060.ea92533bad06b39c7d93742505cbaa50@haskell.org> #10352: Properly link Haskell shared libs on ELF systems -------------------------------------+------------------------------------- Reporter: duncan | Owner: Type: task | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.11 (Linking) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: 5987 Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by trommler): Replying to [comment:10 Phyx-]: > Hmm, but what would the advantages of this be over the proposed solution though? The parameter (or value in the environment variable) would not need to depend on the installation directory (of the RTS libs) but just say '''what''' flavour of RTS is wanted. The advantages are 1. User's don't need to learn the internal organisation of directories, which also might change with releases. 1. In scripts (testcases etc) we do not depend on those directory names either. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 12 08:19:01 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 12 Jul 2016 08:19:01 -0000 Subject: [GHC] #12168: panic! (the 'impossible' happened) with gi-gtk 3.0.4 In-Reply-To: <045.c1a720f41087b515211a480bde1e0805@haskell.org> References: <045.c1a720f41087b515211a480bde1e0805@haskell.org> Message-ID: <060.75c3754bac088a421fc492091531e83f@haskell.org> #12168: panic! (the 'impossible' happened) with gi-gtk 3.0.4 -------------------------------------+------------------------------------- Reporter: drb226 | Owner: 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): I'm not up to reproducing using docker etc (but perhaps someone else may be?). But here are some pointers. * After this: {{{ [599 of 654] Compiling GI.Gtk.Objects.Widget ( GI/Gtk/Objects/Widget.hs, .stack-work/dist/x86_64-linux/Cabal-1.24.0.0/build/GI/Gtk/Objects/Widget.o ) ghc: panic! (the 'impossible' happened) (GHC version 8.0.1 for x86_64-unknown-linux): urk! lookup local fingerprint $fAttrInfoWidgetMarginTopPropertyInfo4 }}} if you compile just that one module `GI.Gtk.Objects.Widget` all by itself (use `-v` to see the command line that stack is using, I guess), does the error repeat? I hope so! * Add `-ddump-simpl` to the command line, which should show the Core that `MkIface` stumbles on. Beyond that I think we may need to start add debug-prints to `MkIface` to get more data. I'm guessing that the strongly-connected component analysis in `MkIface.addFingerprints` is somehow missing an edge. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 12 08:36:39 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 12 Jul 2016 08:36:39 -0000 Subject: [GHC] #12367: Commit adding instances to GHC.Generics regression compiler performance In-Reply-To: <046.87a5f8a842934b4554eedf79fb6bebbc@haskell.org> References: <046.87a5f8a842934b4554eedf79fb6bebbc@haskell.org> Message-ID: <061.255ea864755af43632a14e27b4d71c6b@haskell.org> #12367: Commit adding instances to GHC.Generics regression compiler performance -------------------------------------+------------------------------------- Reporter: bgamari | Owner: bgamari Type: bug | Status: new Priority: normal | Milestone: 8.0.2 Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Generics 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 bgamari): In our call yesterday Simon expressed skepticism that the performance regression is entirely due to a larger interface file. More like, he said, is that an interface is now being loaded which wasn't previously necessary. Indeed this is the case: interface files for both `GHC.Generics` and `GHC.Ptr` are now loaded while compiling `Data.Foldable` but were not previously, {{{ $ grep 'Reading interface' dump-if.log Reading interface for Prelude; reason: Prelude is directly imported Reading interface for Geomfuns; Reading interface for Auxprogfuns; Reading interface for GHC.Base; Reading interface for GHC.Float; Reading interface for GHC.Types; Reading interface for Data.Foldable; Reading interface for GHC.List; Reading interface for GHC.Show; Reading interface for GHC.Prim; Reading interface for GHC.Classes; reason: Need decl for Eq Reading interface for GHC.Num; reason: Need decl for Num Reading interface for GHC.Stack.Types; reason: Need decl for SrcLoc Reading interface for GHC.Integer.Type; Reading interface for GHC.Generics; reason: Need decl for V1 Reading interface for GHC.Ptr; reason: Need decl for Ptr Reading interface for Data.Monoid; reason: Need decl for Sum Reading interface for Data.Proxy; reason: Need decl for Proxy Reading interface for Data.Either; reason: Need decl for Either Reading interface for GHC.Arr; reason: Need decl for Array Reading interface for GHC.Tuple; Reading interface for GHC.Enum; reason: Need decl for enumFromTo Reading interface for GHC.CString; }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 12 08:37:03 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 12 Jul 2016 08:37:03 -0000 Subject: [GHC] #12378: Not enough inlining happens with single-method type classes In-Reply-To: <043.6cfc5337b3b4cd84d2c9380280b0d202@haskell.org> References: <043.6cfc5337b3b4cd84d2c9380280b0d202@haskell.org> Message-ID: <058.f317893cfb9fa9cc69e1399125305636@haskell.org> #12378: Not enough inlining happens with single-method type classes -------------------------------------+------------------------------------- Reporter: akio | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.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 simonpj): I've compiled your program with `-O2`, and both ghc 8.0 and HEAD, and cannot see a top-level definition of type `Small (Either () ())`. Can you compile with `-ddump-simpl`, attach the result, and point to the line number that concerns you? Thanks! Simon -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 12 08:43:07 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 12 Jul 2016 08:43:07 -0000 Subject: [GHC] #393: functions without implementations In-Reply-To: <047.8e9c859b4db83c0d687094f53af0d886@haskell.org> References: <047.8e9c859b4db83c0d687094f53af0d886@haskell.org> Message-ID: <062.1e66481702aadc0758606385d4a78510@haskell.org> #393: functions without implementations -------------------------------------+------------------------------------- Reporter: c_maeder | Owner: Type: feature request | Status: new Priority: normal | Milestone: ⊥ Component: Compiler (Type | Version: None checker) | 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 nomeata): * status: closed => new * resolution: wontfix => Comment: I find Iceland_jack’s examples convincing, and this is a fun nice newcomer task, hence reopening. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 12 09:14:05 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 12 Jul 2016 09:14:05 -0000 Subject: [GHC] #12367: Commit adding instances to GHC.Generics regression compiler performance In-Reply-To: <046.87a5f8a842934b4554eedf79fb6bebbc@haskell.org> References: <046.87a5f8a842934b4554eedf79fb6bebbc@haskell.org> Message-ID: <061.5881df8eda294995ffccb8f5188d9aac@haskell.org> #12367: Commit adding instances to GHC.Generics regression compiler performance -------------------------------------+------------------------------------- Reporter: bgamari | Owner: bgamari Type: bug | Status: new Priority: normal | Milestone: 8.0.2 Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Generics 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 bgamari): It's not entirely clear how to proceed from here. The problem here is that we want to provide `Generic` instances for many types in `base`, while at the same time providing, e.g., `Foldable` and `Monoid` instances for the generic representation types. As far as I can tell we have a few options, 1. Keep the status quo and accept the fact that much of `base` pulls is `GHC.Generics` 2. Move the data types in `GHC.Generics` to a new `GHC.Generics.Internal` module, placing the the instances in `GHC.Generics`. This would mean that `GHC.Generics` would be full of orphans but that fewer modules within `base` would need to import the full bulk of the instances. That being said, this does nothing to help users who use `GHC.Generics` but none of the instances. 3. Wire-in the generics representation types to hopefully avoid the need to pull in the interface file at all when deriving `Generic` (assuming that GHC in fact is capable to avoid pulling in interface files when loading only wired-in declarations). 4. Add `hs-boot` files for `Foldable`, `Traversable`, et al., allowing us to move the instances for the `GHC.Generics` types to `GHC.Generics` 5. Something else? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 12 10:08:51 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 12 Jul 2016 10:08:51 -0000 Subject: [GHC] #12367: Commit adding instances to GHC.Generics regression compiler performance In-Reply-To: <046.87a5f8a842934b4554eedf79fb6bebbc@haskell.org> References: <046.87a5f8a842934b4554eedf79fb6bebbc@haskell.org> Message-ID: <061.bb4048005ad3c7adc08dee7e2346487f@haskell.org> #12367: Commit adding instances to GHC.Generics regression compiler performance -------------------------------------+------------------------------------- Reporter: bgamari | Owner: bgamari Type: bug | Status: new Priority: normal | Milestone: 8.0.2 Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Generics 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): We can't move to a solution until we know WHY `GHC.Ptr` and `GHC.Generics` are being read. Why do we need `V1` and `Ptr` when we didn't before. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 12 11:11:29 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 12 Jul 2016 11:11:29 -0000 Subject: [GHC] #12382: Rename clasing type variables more consistently Message-ID: <046.c5cb956f322074bdfaee0fe12bd9cbb4@haskell.org> #12382: Rename clasing type variables more consistently -------------------------------------+------------------------------------- Reporter: nomeata | Owner: Type: feature | Status: new request | Priority: low | Milestone: Component: Compiler | Version: 8.1 (Type checker) | 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 minor polishing, but polish is nice: Consider {{{ :t (id,id,id) (id,id,id) :: (a -> a, a1 -> a1, a2 -> a2) }}} this looks as if the first `a` is in some way better or more important. What I’d like to see is {{{ :t (id,id,id) (id,id,id) :: (a1 -> a2, a2 -> a2, a3 -> a3) }}} In other words: If two type variables clash and need to be renamed, then rename both (all) of them. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 12 11:11:54 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 12 Jul 2016 11:11:54 -0000 Subject: [GHC] #12382: Rename clasing type variables more consistently In-Reply-To: <046.c5cb956f322074bdfaee0fe12bd9cbb4@haskell.org> References: <046.c5cb956f322074bdfaee0fe12bd9cbb4@haskell.org> Message-ID: <061.af77dc1618e82b8d80860f1452f66f99@haskell.org> #12382: Rename clasing type variables more consistently -------------------------------------+------------------------------------- Reporter: nomeata | Owner: Type: feature request | Status: new Priority: low | Milestone: 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: | -------------------------------------+------------------------------------- Comment (by nomeata): I am having a hard time finding the place where the renaming happens. If that code looks at the type (or at least all type variables bound together) as a whole this might be quite easy. If it just adds one variable by another, without being able to rename the existing ones, it might be hard. Can someone point me to the rough area of the code? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 12 11:23:55 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 12 Jul 2016 11:23:55 -0000 Subject: [GHC] #12370: Implement LetUp in DmdAnal (or document why we do not do it) In-Reply-To: <046.4d0b4649e15ed41a4a32187881ac4332@haskell.org> References: <046.4d0b4649e15ed41a4a32187881ac4332@haskell.org> Message-ID: <061.6683bf074bb177ab6a5ba84e87f307d9@haskell.org> #12370: Implement LetUp in DmdAnal (or document why we do not do it) -------------------------------------+------------------------------------- Reporter: nomeata | Owner: Type: task | Status: patch Priority: normal | Milestone: Component: Compiler | 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): Phab:D2395 Wiki Page: | -------------------------------------+------------------------------------- Comment (by Joachim Breitner ): In [changeset:"45d8f4eb2bf2fcb103517d064e7ba1e491a66f4c/ghc" 45d8f4eb/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="45d8f4eb2bf2fcb103517d064e7ba1e491a66f4c" Demand analyser: Implement LetUp rule (#12370) This makes the implementation match the description in the paper more closely: There, a let binding that is not a function has first its body analised, and then the binding’s RHS. This way, the demand on the bound variable by the body can be fed into the RHS, yielding more precise results. Performance measurements do unfortunately not show significant improvements or regessions. Differential Revision: https://phabricator.haskell.org/D2395 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 12 11:30:46 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 12 Jul 2016 11:30:46 -0000 Subject: [GHC] #12382: Rename clasing type variables more consistently In-Reply-To: <046.c5cb956f322074bdfaee0fe12bd9cbb4@haskell.org> References: <046.c5cb956f322074bdfaee0fe12bd9cbb4@haskell.org> Message-ID: <061.b565ad108d1ee0f22102b16396350168@haskell.org> #12382: Rename clasing type variables more consistently -------------------------------------+------------------------------------- Reporter: nomeata | Owner: Type: feature request | Status: new Priority: low | Milestone: 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: | -------------------------------------+------------------------------------- Comment (by nomeata): Ah, it seems to be `tidyOccName` in `basicTypes/OccName`. I’ll see what can be done here. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 12 11:40:32 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 12 Jul 2016 11:40:32 -0000 Subject: [GHC] #12382: Rename clasing type variables more consistently In-Reply-To: <046.c5cb956f322074bdfaee0fe12bd9cbb4@haskell.org> References: <046.c5cb956f322074bdfaee0fe12bd9cbb4@haskell.org> Message-ID: <061.583d269300699422efba926535fa496b@haskell.org> #12382: Rename clasing type variables more consistently -------------------------------------+------------------------------------- Reporter: nomeata | Owner: Type: feature request | Status: new Priority: low | Milestone: 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: | -------------------------------------+------------------------------------- Comment (by nomeata): Beware of recent performance fixes around `tidyOccName` (changeset:c89bd681d34d3339771ebdde8aa468b1d9ab042b/ghc), which unfortunately does not come with a performance test case. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 12 11:51:32 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 12 Jul 2016 11:51:32 -0000 Subject: [GHC] #12383: ghc: internal error: TSO object entered Message-ID: <047.4cc86cc0c137f15fdedd00b118aa1ed6@haskell.org> #12383: ghc: internal error: TSO object entered -------------------------------------+------------------------------------- Reporter: aufheben | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 Keywords: | Operating System: Linux Architecture: x86_64 | Type of failure: Compile-time (amd64) | crash Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- I just ran into this build failure for the first time: {{{ ghc: internal error: TSO object entered! (GHC version 7.10.3 for x86_64_unknown_linux) Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug }}} I'm not sure how to reproduce this bug or obtain more debugging information but this is how it happened: I was working with Yesod and trying to edit a .hamlet template file. When the file was saved Yesod tried to recompile the project and the build failed with that output. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 12 11:52:01 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 12 Jul 2016 11:52:01 -0000 Subject: [GHC] #12382: Rename clasing type variables more consistently In-Reply-To: <046.c5cb956f322074bdfaee0fe12bd9cbb4@haskell.org> References: <046.c5cb956f322074bdfaee0fe12bd9cbb4@haskell.org> Message-ID: <061.3a33b10d9644878c7f208647a4413fe9@haskell.org> #12382: Rename clasing type variables more consistently -------------------------------------+------------------------------------- Reporter: nomeata | Owner: Type: feature request | Status: new Priority: low | Milestone: 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: | -------------------------------------+------------------------------------- Comment (by nomeata): Fun fact: HEAD hands out numbers in an unexpected order: {{{ Prelude> :t (id,id,id) (id,id,id) :: (a2 -> a2, a1 -> a1, a -> a) }}} This was the other (better?) way around in 7.10. Did not check 8.0. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 12 12:01:31 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 12 Jul 2016 12:01:31 -0000 Subject: [GHC] #12367: Commit adding instances to GHC.Generics regression compiler performance In-Reply-To: <046.87a5f8a842934b4554eedf79fb6bebbc@haskell.org> References: <046.87a5f8a842934b4554eedf79fb6bebbc@haskell.org> Message-ID: <061.e23a59fc67b5db47290cc32af80bf172@haskell.org> #12367: Commit adding instances to GHC.Generics regression compiler performance -------------------------------------+------------------------------------- Reporter: bgamari | Owner: bgamari Type: bug | Status: new Priority: normal | Milestone: 8.0.2 Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Generics 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 bgamari): Simonpj, `GHC.Generics` is read because `Data.Foldable` provides a `Foldable` instance for `GHC.Generics.V1`. `GHC.Ptr` is read because `GHC.Generics` needs `GHC.Ptr.Ptr` to define instances for representing `Addr#` fields. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 12 12:01:45 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 12 Jul 2016 12:01:45 -0000 Subject: [GHC] #12367: Commit adding instances to GHC.Generics regression compiler performance In-Reply-To: <046.87a5f8a842934b4554eedf79fb6bebbc@haskell.org> References: <046.87a5f8a842934b4554eedf79fb6bebbc@haskell.org> Message-ID: <061.21e3932b232b02c905bb6b5b126a392b@haskell.org> #12367: Commit adding instances to GHC.Generics regression compiler performance -------------------------------------+------------------------------------- Reporter: bgamari | Owner: bgamari Type: bug | Status: new Priority: normal | Milestone: 8.0.2 Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Generics 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): * cc: bgamari (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 12 13:13:42 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 12 Jul 2016 13:13:42 -0000 Subject: [GHC] #12382: Rename clashing type variables more consistently (was: Rename clasing type variables more consistently) In-Reply-To: <046.c5cb956f322074bdfaee0fe12bd9cbb4@haskell.org> References: <046.c5cb956f322074bdfaee0fe12bd9cbb4@haskell.org> Message-ID: <061.38f259c52c0e633fd9ae60c15634fa05@haskell.org> #12382: Rename clashing type variables more consistently -------------------------------------+------------------------------------- Reporter: nomeata | Owner: Type: feature request | Status: new Priority: low | Milestone: 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: | -------------------------------------+------------------------------------- -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 12 13:31:56 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 12 Jul 2016 13:31:56 -0000 Subject: [GHC] #10352: Properly link Haskell shared libs on ELF systems In-Reply-To: <045.f54c0b53e462b1ea305eb5f3c38d7688@haskell.org> References: <045.f54c0b53e462b1ea305eb5f3c38d7688@haskell.org> Message-ID: <060.de82977740032774686d7f7305de91cf@haskell.org> #10352: Properly link Haskell shared libs on ELF systems -------------------------------------+------------------------------------- Reporter: duncan | Owner: Type: task | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.11 (Linking) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: 5987 Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonmar): I'd rather rely on the usual mechanisms for finding shared library dependencies, so that the user can override them if they want to, using `LD_LIBRARY_PATH` and `LD_PRELOAD` for example. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 12 13:39:22 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 12 Jul 2016 13:39:22 -0000 Subject: [GHC] #12212: GHC 8.0.1 crash In-Reply-To: <047.6638412a065ad4919512719a751245d5@haskell.org> References: <047.6638412a065ad4919512719a751245d5@haskell.org> Message-ID: <062.d404366afd3bce2a1a2eab61423d58aa@haskell.org> #12212: GHC 8.0.1 crash -------------------------------------+------------------------------------- Reporter: dibblego | Owner: Type: bug | Status: closed Priority: normal | Milestone: 8.0.2 Component: Compiler | Version: 8.0.1 Resolution: fixed | Keywords: Operating System: Linux | Architecture: | Unknown/Multiple Type of failure: Compile-time | Test Case: crash | simplCore/should_compile/T12212 Blocked By: | Blocking: Related Tickets: 9160, 10602 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: merge => closed * resolution: => fixed * milestone: => 8.0.2 Comment: Merged to `ghc-8.0` as 3ee5eedf87a13e720b97112517ce250046879eaa. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 12 13:40:04 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 12 Jul 2016 13:40:04 -0000 Subject: [GHC] #11690: stage 1 compiler silently ignores plugins In-Reply-To: <043.6bb550c2fb8b0e3c6348c8759d6a0132@haskell.org> References: <043.6bb550c2fb8b0e3c6348c8759d6a0132@haskell.org> Message-ID: <058.6a83a6ef492b04b8833a4b872ca6fc14@haskell.org> #11690: stage 1 compiler silently ignores plugins -------------------------------------+------------------------------------- Reporter: osa1 | Owner: osa1 Type: feature request | Status: closed Priority: lowest | Milestone: 8.0.2 Component: Compiler | Version: 7.10.3 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:D2334 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: merge => closed * resolution: => fixed * milestone: => 8.0.2 Comment: Merged to `ghc-8.0` as df4323bccbe26205e7100af2292501b9c903e71c. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 12 13:41:50 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 12 Jul 2016 13:41:50 -0000 Subject: [GHC] #12007: Panic when loading file with nested pattern synonyms into ghci In-Reply-To: <050.6ea75b00ffb245107acfb719a89b7ff6@haskell.org> References: <050.6ea75b00ffb245107acfb719a89b7ff6@haskell.org> Message-ID: <065.8615e0d244be53e333470947d8b11762@haskell.org> #12007: Panic when loading file with nested pattern synonyms into ghci -------------------------------------+------------------------------------- Reporter: MikeIzbicki | Owner: Type: bug | Status: merge Priority: normal | Milestone: Component: Compiler | Version: 8.1 Resolution: | Keywords: | PatternSynonyms Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | ghci/scripts/T12007 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): Merged to `ghc-8.0` as 726d1ddba45d24c998ae378ed5e688a2d24665e7. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 12 13:42:14 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 12 Jul 2016 13:42:14 -0000 Subject: [GHC] #12007: Panic when loading file with nested pattern synonyms into ghci In-Reply-To: <050.6ea75b00ffb245107acfb719a89b7ff6@haskell.org> References: <050.6ea75b00ffb245107acfb719a89b7ff6@haskell.org> Message-ID: <065.e5f18cb47908d90e6b7e0d31dd5bcdea@haskell.org> #12007: Panic when loading file with nested pattern synonyms into ghci -------------------------------------+------------------------------------- Reporter: MikeIzbicki | Owner: Type: bug | Status: merge Priority: normal | Milestone: 8.0.2 Component: Compiler | Version: 8.1 Resolution: | Keywords: | PatternSynonyms Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | ghci/scripts/T12007 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * milestone: => 8.0.2 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 12 13:43:44 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 12 Jul 2016 13:43:44 -0000 Subject: [GHC] #12094: Unlifted types and pattern synonym signatures In-Reply-To: <043.12e14a4dec3cc62adda5e9a020766697@haskell.org> References: <043.12e14a4dec3cc62adda5e9a020766697@haskell.org> Message-ID: <058.de6ee6a88acd558c4b7985cb71a7a9d5@haskell.org> #12094: Unlifted types and pattern synonym signatures -------------------------------------+------------------------------------- Reporter: akio | Owner: Type: bug | Status: closed Priority: normal | Milestone: 8.0.2 Component: Compiler (Type | Version: 8.0.1 checker) | Keywords: Resolution: fixed | PatternSynonyms 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:D2255 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: merge => closed * resolution: => fixed * milestone: => 8.0.2 Comment: Merged to `ghc-8.0` as 04d05617e98f6cb4062aaf405055821e6a09fbbd. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 12 13:46:14 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 12 Jul 2016 13:46:14 -0000 Subject: [GHC] #12026: Pattern match failure in RnNames.hs In-Reply-To: <045.d07f9d8741d68e74ac677773a1b56b31@haskell.org> References: <045.d07f9d8741d68e74ac677773a1b56b31@haskell.org> Message-ID: <060.5fd782d240623362f4b681891a2d4c6a@haskell.org> #12026: Pattern match failure in RnNames.hs -------------------------------------+------------------------------------- Reporter: davean | Owner: mpickering Type: bug | Status: closed Priority: highest | Milestone: 8.0.2 Component: Compiler | Version: 8.0.1 Resolution: fixed | 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:D2181 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: merge => closed * resolution: => fixed Comment: Merged to `ghc-8.0` as 638c1d43b6f7258a5f1936482f11d30b6b089c1d. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 12 13:47:56 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 12 Jul 2016 13:47:56 -0000 Subject: [GHC] #11554: Self quantification in GADT data declarations In-Reply-To: <046.bec85a0842a04f6c9921baff0e29a2a1@haskell.org> References: <046.bec85a0842a04f6c9921baff0e29a2a1@haskell.org> Message-ID: <061.2aece4cb2cae16658fa785ea01f52e24@haskell.org> #11554: Self quantification in GADT data declarations -------------------------------------+------------------------------------- Reporter: Rafbill | Owner: Type: bug | Status: closed Priority: high | Milestone: 8.0.2 Component: Compiler (Type | Version: 8.0.1-rc2 checker) | Resolution: fixed | Keywords: TypeInType Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: merge => closed * resolution: => fixed Comment: Merged as e2335ea283eb05a78fe962d6a00faefacad2292d. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 12 13:57:55 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 12 Jul 2016 13:57:55 -0000 Subject: [GHC] #12127: ghc-8.0.1: panic! (the 'impossible' happened) filterImports/combine (double import) In-Reply-To: <045.ae5844a0544b94191ee992f204e3d334@haskell.org> References: <045.ae5844a0544b94191ee992f204e3d334@haskell.org> Message-ID: <060.69bea6c4edb580f37940d1e961862512@haskell.org> #12127: ghc-8.0.1: panic! (the 'impossible' happened) filterImports/combine (double import) -------------------------------------+------------------------------------- Reporter: slyfox | Owner: Type: bug | Status: closed Priority: high | Milestone: 8.0.2 Component: Compiler | Version: 8.0.1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: GHC rejects | Test Case: valid program | rename/should_compile/T12127 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: merge => closed * resolution: => fixed Comment: Merged to `ghc-8.0` as 09a46035a1be854f8209416cabcaf907717b4167. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 12 14:02:41 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 12 Jul 2016 14:02:41 -0000 Subject: [GHC] #12130: ghc: panic! (the 'impossible' happened): find_tycon Block [] In-Reply-To: <044.523b434f5130bcce5d2e71f45a4abdd5@haskell.org> References: <044.523b434f5130bcce5d2e71f45a4abdd5@haskell.org> Message-ID: <059.68d1302d7eb4c7fb909865efdceb92ea@haskell.org> #12130: ghc: panic! (the 'impossible' happened): find_tycon Block [] -------------------------------------+------------------------------------- Reporter: jeiea | Owner: adamgundry Type: bug | Status: closed Priority: high | Milestone: 8.0.2 Component: Template Haskell | Version: 8.0.1 Resolution: fixed | Keywords: | DisambiguateRecordFields Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: th/T12130 Blocked By: | Blocking: Related Tickets: #11228 | Differential Rev(s): Phab:D2321 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: merge => closed * resolution: => fixed Comment: Merged to `ghc-8.0` as 206ac693372d00b59eb98c34b801906c5e7bedfc. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 12 14:03:31 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 12 Jul 2016 14:03:31 -0000 Subject: [GHC] #12082: Typeable on RealWorld fails In-Reply-To: <046.e4ee4338a41502e1434038b393cfe130@haskell.org> References: <046.e4ee4338a41502e1434038b393cfe130@haskell.org> Message-ID: <061.2ebd300d117c4121760f799e77c10bbd@haskell.org> #12082: Typeable on RealWorld fails -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: bug | Status: closed Priority: high | Milestone: 8.0.2 Component: Compiler | Version: 8.0.1 Resolution: fixed | Keywords: Typeable Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | typecheck/should_run/TypeRep Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2240, Wiki Page: | Phab:D2239 -------------------------------------+------------------------------------- Changes (by bgamari): * status: merge => closed * resolution: => fixed Comment: Merged to `ghc-8.0` as 2c5a5fc14300e1615bde63f4ba63c98727442061. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 12 14:04:26 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 12 Jul 2016 14:04:26 -0000 Subject: [GHC] #12156: -fdefer-typed-holes causes panic on unbound variable In-Reply-To: <043.3614ae54ff3ca0baba5007f775728ec4@haskell.org> References: <043.3614ae54ff3ca0baba5007f775728ec4@haskell.org> Message-ID: <058.423aae3dbe4301e441119764b013b851@haskell.org> #12156: -fdefer-typed-holes causes panic on unbound variable -------------------------------------+------------------------------------- Reporter: osa1 | Owner: Type: bug | Status: closed Priority: high | Milestone: 8.0.2 Component: Compiler (Type | Version: 8.1 checker) | Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: partial- | sigs/should_compile/T12156 Blocked By: | Blocking: Related Tickets: #10569 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: merge => closed * resolution: => fixed Comment: Merged to `ghc-8.0` as 8de6c607321cdf36336ccab311357c111e895e54. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 12 14:04:37 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 12 Jul 2016 14:04:37 -0000 Subject: [GHC] #12156: -fdefer-typed-holes causes panic on unbound variable In-Reply-To: <043.3614ae54ff3ca0baba5007f775728ec4@haskell.org> References: <043.3614ae54ff3ca0baba5007f775728ec4@haskell.org> Message-ID: <058.d7d395214b6152ed5d93fd68ab3716e1@haskell.org> #12156: -fdefer-typed-holes causes panic on unbound variable -------------------------------------+------------------------------------- Reporter: osa1 | Owner: Type: bug | Status: closed Priority: high | Milestone: 8.0.2 Component: Compiler (Type | Version: 8.0.1 checker) | Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: partial- | sigs/should_compile/T12156 Blocked By: | Blocking: Related Tickets: #10569 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * version: 8.1 => 8.0.1 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 12 14:06:07 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 12 Jul 2016 14:06:07 -0000 Subject: [GHC] #8308: Resurrect ticky code for counting constructor arity In-Reply-To: <048.881ed81a50f663ce5516d17888eb822c@haskell.org> References: <048.881ed81a50f663ce5516d17888eb822c@haskell.org> Message-ID: <063.d533953b2e8a1816ef95cbeda0f84b22@haskell.org> #8308: Resurrect ticky code for counting constructor arity ------------------------------+-------------------------------------------- Reporter: jstolarek | Owner: Type: task | Status: closed Priority: normal | Milestone: 8.0.2 Component: Profiling | Version: 7.7 Resolution: fixed | Keywords: newcomer Operating System: Windows | Architecture: Unknown/Multiple Type of failure: Other | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D931 Phab:D2318 Wiki Page: | ------------------------------+-------------------------------------------- Changes (by bgamari): * status: merge => closed Comment: Merged both the ticky fix and the subsequent Windows fix to `ghc-8.0`. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 12 14:06:40 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 12 Jul 2016 14:06:40 -0000 Subject: [GHC] #10647: Notice about lack of SIMD support. In-Reply-To: <044.41ea1589882067bc6ce5e3c65bf3dab1@haskell.org> References: <044.41ea1589882067bc6ce5e3c65bf3dab1@haskell.org> Message-ID: <059.88f566b5b515b6831f1201d78d5ef9cf@haskell.org> #10647: Notice about lack of SIMD support. -------------------------------------+------------------------------------- Reporter: mniip | Owner: Type: bug | Status: closed Priority: normal | Milestone: 8.0.2 Component: Compiler | Version: 7.8.4 Resolution: fixed | Keywords: Operating System: Linux | Architecture: x86_64 Type of failure: Compile-time | (amd64) 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.0` as 868ee5b3ad30906ef50d15cced531b8131be04b1. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 12 14:16:03 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 12 Jul 2016 14:16:03 -0000 Subject: [GHC] #11835: ApplicativeDo failed to desugar last line with pure $ In-Reply-To: <045.10a09841bc3d481ea24884cfac477277@haskell.org> References: <045.10a09841bc3d481ea24884cfac477277@haskell.org> Message-ID: <060.1097fb502a955f94bc9e1452a287362e@haskell.org> #11835: ApplicativeDo failed to desugar last line with pure $ -------------------------------------+------------------------------------- Reporter: Cosmia | Owner: simonmar Type: bug | Status: closed Priority: normal | Milestone: 8.0.2 Component: Compiler | Version: 8.0.1-rc2 Resolution: fixed | Keywords: ApplicativeDo Operating System: MacOS X | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: #11607 | Differential Rev(s): Phab:D2345 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: merge => closed * resolution: => fixed Comment: Merged comment:11 and comment:9 to `ghc-8.0`. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 12 14:18:28 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 12 Jul 2016 14:18:28 -0000 Subject: [GHC] #12080: RebindableSyntax breaks deriving Ord In-Reply-To: <046.7713328ee376d4dd3d58a4520e76a2fb@haskell.org> References: <046.7713328ee376d4dd3d58a4520e76a2fb@haskell.org> Message-ID: <061.885db5d042bd11b2d751d4c29649aa13@haskell.org> #12080: RebindableSyntax breaks deriving Ord -------------------------------------+------------------------------------- Reporter: afarmer | Owner: afarmer Type: bug | Status: closed Priority: normal | Milestone: 8.0.2 Component: Compiler | Version: 7.10.3 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #11396 | Differential Rev(s): Phab:D2247 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: merge => closed * resolution: => fixed Comment: Merged to `ghc-8.0` as cd5c5c3f3b0c63240058efe96cb12079fb03133e. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 12 14:50:46 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 12 Jul 2016 14:50:46 -0000 Subject: [GHC] #12382: Rename clashing type variables more consistently In-Reply-To: <046.c5cb956f322074bdfaee0fe12bd9cbb4@haskell.org> References: <046.c5cb956f322074bdfaee0fe12bd9cbb4@haskell.org> Message-ID: <061.4ff35125fd93aa4bf2a223a19449ee4b@haskell.org> #12382: Rename clashing type variables more consistently -------------------------------------+------------------------------------- Reporter: nomeata | Owner: nomeata Type: feature request | Status: new Priority: low | Milestone: 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 nomeata): * owner: => nomeata Comment: Some preparational work in `wip/T12382`. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 12 15:27:07 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 12 Jul 2016 15:27:07 -0000 Subject: [GHC] #12381: Type family not reduced In-Reply-To: <046.0dea1b11f4af8f3cac37c083d6847cd7@haskell.org> References: <046.0dea1b11f4af8f3cac37c083d6847cd7@haskell.org> Message-ID: <061.ffb18dad0a07320d00d51b7f64419ade@haskell.org> #12381: Type family not reduced -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: bug | Status: merge Priority: normal | Milestone: 8.0.2 Component: Compiler (Type | Version: 8.0.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 Tue Jul 12 15:30:46 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 12 Jul 2016 15:30:46 -0000 Subject: [GHC] #12384: Type family not reduced, again Message-ID: <047.4aa60b42d6ca7ab25500fb26e0021c6b@haskell.org> #12384: Type family not reduced, again -------------------------------------+------------------------------------- Reporter: kosmikus | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Keywords: | Operating System: Linux Architecture: | Type of failure: GHC rejects Unknown/Multiple | valid program Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- This one looks similar to #12381, but unfortunately, it does not seem to be fixed in HEAD: {{{#!hs {-# LANGUAGE TypeInType, TypeFamilies, FlexibleInstances #-} import GHC.Types type family F (a :: Type) :: Type class C a where type D (a :: Type) :: F a instance (F a ~ Bool) => C a where type D a = True }}} This yields (in 8.0.1 and 8.1.20160709): {{{ Constraint.hs:11:14: error: • Expected kind ‘F a’, but ‘'True’ has kind ‘Bool’ • In the type ‘True’ In the type instance declaration for ‘D’ In the instance declaration for ‘C a’ }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 12 15:31:26 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 12 Jul 2016 15:31:26 -0000 Subject: [GHC] #12385: Another case of type families not being reduced Message-ID: <046.c479f094dbc1b0af958bcb72c61ff3aa@haskell.org> #12385: Another case of type families not being reduced -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: bug | Status: new Priority: normal | Milestone: 8.0.2 Component: Compiler | Version: 8.0.1 (Type checker) | 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: -------------------------------------+------------------------------------- Similar to #12381 and #11348 but this one doesn't pass with GHC HEAD either, {{{#!hs {-# LANGUAGE TypeInType, TypeFamilies, FlexibleInstances #-} import GHC.Types type family F (a :: Type) :: Type class C a where type D (a :: Type) :: F a instance (F a ~ Bool) => C a where type D a = True }}} fails with, {{{ Hi.hs:11:14: error: • Expected kind ‘F a’, but ‘'True’ has kind ‘Bool’ • In the type ‘True’ In the type instance declaration for ‘D’ In the instance declaration for ‘C a’ }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 12 15:31:46 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 12 Jul 2016 15:31:46 -0000 Subject: [GHC] #12384: Type family not reduced, again In-Reply-To: <047.4aa60b42d6ca7ab25500fb26e0021c6b@haskell.org> References: <047.4aa60b42d6ca7ab25500fb26e0021c6b@haskell.org> Message-ID: <062.9cf7e05f93e5a3dac91aa4e8e375d45f@haskell.org> #12384: Type family not reduced, again -------------------------------------+------------------------------------- Reporter: kosmikus | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Linux | 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 kosmikus: @@ -14,1 +14,1 @@ - type D a = True + type D a = True New description: This one looks similar to #12381, but unfortunately, it does not seem to be fixed in HEAD: {{{#!hs {-# LANGUAGE TypeInType, TypeFamilies, FlexibleInstances #-} import GHC.Types type family F (a :: Type) :: Type class C a where type D (a :: Type) :: F a instance (F a ~ Bool) => C a where type D a = True }}} This yields (in 8.0.1 and 8.1.20160709): {{{ Constraint.hs:11:14: error: • Expected kind ‘F a’, but ‘'True’ has kind ‘Bool’ • In the type ‘True’ In the type instance declaration for ‘D’ In the instance declaration for ‘C a’ }}} -- -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 12 15:32:21 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 12 Jul 2016 15:32:21 -0000 Subject: [GHC] #12385: Another case of type families not being reduced In-Reply-To: <046.c479f094dbc1b0af958bcb72c61ff3aa@haskell.org> References: <046.c479f094dbc1b0af958bcb72c61ff3aa@haskell.org> Message-ID: <061.1e19f4af0e10c24db3db48e7b3baa367@haskell.org> #12385: Another case of type families not being reduced -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: bug | Status: closed Priority: normal | Milestone: 8.0.2 Component: Compiler (Type | Version: 8.0.1 checker) | Resolution: duplicate | 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: => duplicate Comment: Kosmikus beat me to reporting this. This is a duplicate of #12384. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 12 17:44:16 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 12 Jul 2016 17:44:16 -0000 Subject: [GHC] #12386: Infinite loop when showing type family error Message-ID: <047.61d384525fef8c0da8d7346e45b629d6@haskell.org> #12386: Infinite loop when showing type family error -------------------------------------+------------------------------------- Reporter: elliottt | Owner: 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: -------------------------------------+------------------------------------- When attempting to load this code in ghci with ghc-8.0.1, I get an infinite loop while it attempts to display the error: {{{ {-# LANGUAGE TypeFamilies #-} class C a where type family F a t :: * type family T a :: * type T a = F a }}} {{{ catbug :: ~/Scratch/ast-experiment » ghci test.hs GHCi, version 8.0.1: http://www.haskell.org/ghc/ :? for help Loaded GHCi configuration from /Users/trevor/.ghci [1 of 1] Compiling Main ( test.hs, interpreted ) test.hs:7:14: error: }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 12 20:11:50 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 12 Jul 2016 20:11:50 -0000 Subject: [GHC] #12384: Type family not reduced, again In-Reply-To: <047.4aa60b42d6ca7ab25500fb26e0021c6b@haskell.org> References: <047.4aa60b42d6ca7ab25500fb26e0021c6b@haskell.org> Message-ID: <062.4d476cf236bbe26091b5689158cb17b8@haskell.org> #12384: Type family not reduced, again -------------------------------------+------------------------------------- Reporter: kosmikus | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Linux | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by alexvieth): #12381 and #11348 were all about the order in which instance declarations are checked, but this case seems to be something different. Here there's no choice but to check these declarations in the order that they're written: the type family, then the class, then the instance of that class. I suppose the type of `D ()` should be `(F a ~ Bool) => True` but as far as I know GHC can't handle such a thing. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 13 00:03:23 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 13 Jul 2016 00:03:23 -0000 Subject: [GHC] #12387: Template Haskell ignores class instance definitions with methods that don't belong to the class Message-ID: <050.eb69c313a059df9b62466d07df30fd0b@haskell.org> #12387: Template Haskell ignores class instance definitions with methods that don't belong to the class -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Template | Version: 8.0.1 Haskell | 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: -------------------------------------+------------------------------------- {{{#!hs {-# LANGUAGE TemplateHaskell #-} {-# OPTIONS_GHC -ddump-splices #-} module Main where import Language.Haskell.TH.Lib data Foo = Foo $(do d <- instanceD (cxt []) (conT ''Eq `appT` conT ''Foo) [funD 'compare [clause [] (normalB $ varE 'undefined) []]] return [d]) main :: IO () main = print $ Foo == Foo }}} {{{ $ /opt/ghc/8.0.1/bin/runghc Bug.hs Bug.hs:(9,3)-(11,15): Splicing declarations do { d_a2hL <- instanceD (cxt []) (conT ''Eq `appT` conT ''Foo) [funD 'compare [clause [] (normalB $ varE 'undefined) []]]; return [d_a2hL] } ======> instance Eq Foo where compare = undefined Bug.hs:9:3: warning: [-Wmissing-methods] • No explicit implementation for either ‘==’ or ‘/=’ • In the instance declaration for ‘Eq Foo’ Bug.hs: stack overflow }}} `compare` obviously doesn't belong to `Eq`, yet GHC happily accepts an `Eq Foo` instance with a definition for `compare`! Worse yet, there's now neither a definition for `(==)` nor `(/=)`, so the default definition of `(==)` triggers an infinite loop, blowing the stack at runtime. I don't know how pervasive this bug is. That is, I'm not sure if you could also attach associated type family instances, pattern synonyms, etc. that don't belong to the class either. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 13 04:59:36 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 13 Jul 2016 04:59:36 -0000 Subject: [GHC] #781: GHCi on x86_64, cannot link to static data in shared libs In-Reply-To: <044.a73c522b97030f99c5fa39d521657f06@haskell.org> References: <044.a73c522b97030f99c5fa39d521657f06@haskell.org> Message-ID: <059.077749c96812663365f70b2104cabdd2@haskell.org> #781: GHCi on x86_64, cannot link to static data in shared libs -------------------------------------+------------------------------------- Reporter: guest | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Runtime System | Version: 6.5 (Linker) | Keywords: Resolution: | getEnvironment Operating System: Linux | Architecture: x86_64 | (amd64) Type of failure: GHCi crash | Test Case: | getEnvironment01 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by dobenour): Could the RTS linker distinguish code and data references the way the system dynamic linker does? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 13 05:06:33 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 13 Jul 2016 05:06:33 -0000 Subject: [GHC] #12388: Don't barf on failures in the RTS linker Message-ID: <047.b86bfd9a8524336c9591b8a2b9e093dd@haskell.org> #12388: Don't barf on failures in the RTS linker -------------------------------------+------------------------------------- Reporter: dobenour | Owner: Type: bug | Status: new Priority: normal | Milestone: 8.2.1 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: -------------------------------------+------------------------------------- The RTS linker currently calls `barf()` when it fails. This is a problem because: 1. It appears that there is a bug in GHC, when there is no bug. 2. Failures to load code really should be recoverable. According to a `TODO` in the code, the culprit is resource deallocation, which is very difficult due to the code being written in C and having complicated control flow. There are a few solutions: - Port the RTS linker to C++ and use RAII for resource management. Failures would be handled (internally to the linker) by throwing a C++ exception. This is actually my favorite, but might not be popular with the GHC devs. - Build a huge context struct containing all needed resources and free it before returning. Signal errors with `longjmp()`. - Try to find each and every place where resources need to be free, and free them by hand. Signal errors with return codes. This seems too error-prone. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 13 09:46:30 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 13 Jul 2016 09:46:30 -0000 Subject: [GHC] #781: GHCi on x86_64, cannot link to static data in shared libs In-Reply-To: <044.a73c522b97030f99c5fa39d521657f06@haskell.org> References: <044.a73c522b97030f99c5fa39d521657f06@haskell.org> Message-ID: <059.de75794519224283f690737a708a3bf5@haskell.org> #781: GHCi on x86_64, cannot link to static data in shared libs -------------------------------------+------------------------------------- Reporter: guest | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Runtime System | Version: 6.5 (Linker) | Keywords: Resolution: | getEnvironment Operating System: Linux | Architecture: x86_64 | (amd64) Type of failure: GHCi crash | Test Case: | getEnvironment01 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonmar): Possibly... I think I looked into it but couldn't find a way to do it, but that may have changed. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 13 14:17:55 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 13 Jul 2016 14:17:55 -0000 Subject: [GHC] #12382: Rename clashing type variables more consistently In-Reply-To: <046.c5cb956f322074bdfaee0fe12bd9cbb4@haskell.org> References: <046.c5cb956f322074bdfaee0fe12bd9cbb4@haskell.org> Message-ID: <061.c6e5db55a5d0c633f6dc519c50620360@haskell.org> #12382: Rename clashing type variables more consistently -------------------------------------+------------------------------------- Reporter: nomeata | Owner: nomeata Type: feature request | Status: patch Priority: low | Milestone: 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:D2402 Wiki Page: | -------------------------------------+------------------------------------- Changes (by nomeata): * status: new => patch * differential: => Phab:D2402 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 13 15:04:36 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 13 Jul 2016 15:04:36 -0000 Subject: [GHC] #12081: TypeInType Compile-time Panic In-Reply-To: <047.ceeb8e791a978943694d6a174084488b@haskell.org> References: <047.ceeb8e791a978943694d6a174084488b@haskell.org> Message-ID: <062.d534890b22866dc8f1315093196bee13@haskell.org> #12081: TypeInType Compile-time Panic -------------------------------------+------------------------------------- Reporter: MichaelK | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1-rc4 Resolution: | Keywords: TypeInType Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by MitchellSalad): I happened to hit this same panic with a simpler example: {{{#!hs {-# LANGUAGE DataKinds #-} {-# LANGUAGE ExistentialQuantification #-} {-# LANGUAGE KindSignatures #-} {-# LANGUAGE TypeInType #-} data Foo = forall (x :: Foo). Bar x }}} fails with: {{{ ghc: panic! (the 'impossible' happened) (GHC version 8.0.1 for x86_64-unknown-linux): isInjectiveTyCon sees a TcTyCon Foo }}} Without -XTypeInType, it fails with: {{{ foo.hs:5:25: error: • Type constructor ‘Foo’ cannot be used here (Perhaps you intended to use TypeInType) • In the kind ‘Foo’ In the definition of data constructor ‘Bar’ In the data declaration for ‘Foo’ }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 13 19:56:53 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 13 Jul 2016 19:56:53 -0000 Subject: [GHC] #12081: TypeInType Compile-time Panic In-Reply-To: <047.ceeb8e791a978943694d6a174084488b@haskell.org> References: <047.ceeb8e791a978943694d6a174084488b@haskell.org> Message-ID: <062.7550a37555a2a5955e5767d42544ae87@haskell.org> #12081: TypeInType Compile-time Panic -------------------------------------+------------------------------------- Reporter: MichaelK | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1-rc4 Resolution: | Keywords: TypeInType Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by jstolarek): * cc: jstolarek (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 13 20:45:12 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 13 Jul 2016 20:45:12 -0000 Subject: [GHC] #12389: Limit duplicate export warnings for datatypes Message-ID: <045.b9512948fd651abba4c3deecd83cbcfe@haskell.org> #12389: Limit duplicate export warnings for datatypes -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: Type: feature | Status: new request | Priority: normal | Milestone: 8.2.1 Component: Compiler | Version: 7.10.3 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: Incorrect Unknown/Multiple | warning at compile-time Test Case: | Blocked By: Blocking: | Related Tickets: #11959 Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- `containers` sometimes exports data constructors/patterns conditionally (depending on GHC version and whether `TESTING` is defined). Presently, to avoid a duplicate export warning, it's necessary to write a separate export line for each combination of exported constructors, which is horrible: {{{#!hs module Foo ( #ifdef TESTING #ifdef USE_PATTERN_SYNONYMS Foo (Foo, Pat1, Pat2) #else Foo (Foo) #endif #elif USE_PATTERN_SYNONYMS Foo (Pat1, Pat2) #else Foo #endif }}} or to break up the lines with CPP, which is so horrible I can't even bring myself to write it. I'd much rather be able to write {{{#!hs module Foo ( Foo #ifdef TESTING ,Foo(Foo) #endif #ifdef USE_PATTERN_SYNONYMS ,Foo(Pat1, Pat2) #endif ) }}} The trouble here is that GHC warns about duplicate export of the type `Foo`. I think there's a pretty simple partial solution: only warn about a type export that is *completely* redundant, adding neither type constructor nor pattern. And offer a way to turn off the redundant export warning entirely for types and classes without turning it off for bindings. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 13 20:57:16 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 13 Jul 2016 20:57:16 -0000 Subject: [GHC] #12389: Limit duplicate export warnings for datatypes In-Reply-To: <045.b9512948fd651abba4c3deecd83cbcfe@haskell.org> References: <045.b9512948fd651abba4c3deecd83cbcfe@haskell.org> Message-ID: <060.560f58fc0672f9ba57afe304c8f8afc8@haskell.org> #12389: Limit duplicate export warnings for datatypes -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: Type: feature request | Status: new Priority: normal | Milestone: 8.2.1 Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: #11959 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by rwbarton): Well the first `Foo` export certainly looks redundant (as long as at least one of the CPP flags is enabled). I don't really see how your second version is any better than what you say is "so horrible [...]": {{{#!hs module Foo ( Foo ( #ifdef TESTING Foo, #endif #ifdef USE_PATTERN_SYNONYMS Pat1, Pat2, #endif ) ) }}} (A trailing comma is legal here right? Otherwise it really is a mess.) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 13 21:00:26 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 13 Jul 2016 21:00:26 -0000 Subject: [GHC] #12389: Limit duplicate export warnings for datatypes In-Reply-To: <045.b9512948fd651abba4c3deecd83cbcfe@haskell.org> References: <045.b9512948fd651abba4c3deecd83cbcfe@haskell.org> Message-ID: <060.ab3bcd38963fcff95e1c78c2b04663b9@haskell.org> #12389: Limit duplicate export warnings for datatypes -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: Type: feature request | Status: new Priority: normal | Milestone: 8.2.1 Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: #11959 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by dfeuer): Replying to [comment:1 rwbarton]: > Well the first `Foo` export certainly looks redundant (as long as at least one of the CPP flags is enabled). > > I don't really see how your second version is any better than what you say is "so horrible [...]": > {{{#!hs > module Foo ( > Foo ( > #ifdef TESTING > Foo, > #endif > #ifdef USE_PATTERN_SYNONYMS > Pat1, Pat2, > #endif > ) > ) > }}} > > (A trailing comma is legal here right? Otherwise it really is a mess.) I don't know about GHC 8, but in 7.10, a trailing comma is *not* legal, and neither is a leading one. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 13 21:03:41 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 13 Jul 2016 21:03:41 -0000 Subject: [GHC] #12389: Limit duplicate export warnings for datatypes In-Reply-To: <045.b9512948fd651abba4c3deecd83cbcfe@haskell.org> References: <045.b9512948fd651abba4c3deecd83cbcfe@haskell.org> Message-ID: <060.9ef927ac96159a7aa4bb6ef5bed93ab6@haskell.org> #12389: Limit duplicate export warnings for datatypes -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: Type: feature request | Status: new Priority: normal | Milestone: 8.2.1 Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: #11959 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by rwbarton): Hmm, it's not (in 8 either). A trailing comma is legal at the end of the export list though. Seems like we should just allow it at the end of a constructor/etc. list also. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 13 21:07:57 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 13 Jul 2016 21:07:57 -0000 Subject: [GHC] #12389: Limit duplicate export warnings for datatypes In-Reply-To: <045.b9512948fd651abba4c3deecd83cbcfe@haskell.org> References: <045.b9512948fd651abba4c3deecd83cbcfe@haskell.org> Message-ID: <060.9cec1234162064d4ddadbf6ea16a8db8@haskell.org> #12389: Limit duplicate export warnings for datatypes -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: Type: feature request | Status: new Priority: normal | Milestone: 8.2.1 Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: #11959 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by dfeuer): Sure. That would solve (much of) the problem. I'd want leading commas too, because I tend to prefer a leading-comma style. And I'd want to silence the warning from duplicate constructors/patterns within the list. Because I could, hypothetically, have {{{#!hs Foo ( #if Condition1 Foo, Bar #endif #if Condition2 , Bar, Baz #endif ) }}} and wouldn't want to have to get fancy with the CPP if `Condition1` and `Condition2` both happen to hold. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 13 21:36:06 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 13 Jul 2016 21:36:06 -0000 Subject: [GHC] #12389: Limit duplicate export warnings for datatypes In-Reply-To: <045.b9512948fd651abba4c3deecd83cbcfe@haskell.org> References: <045.b9512948fd651abba4c3deecd83cbcfe@haskell.org> Message-ID: <060.06095e82d5801be76b5dd428bd618ef0@haskell.org> #12389: Limit duplicate export warnings for datatypes -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: Type: feature request | Status: new Priority: normal | Milestone: 8.2.1 Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: #11959 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by rwbarton): Well you don't really want to "silence the warning from duplicate constructors/patterns within the list". You want to silence ''this'' duplicate of `Bar`. If you happen to repeat a different constructor elsewhere in the export list by accident, you'd still want a warning about that. So it would more appropriate to use a mechanism for locally disabling warnings. Since you can already write what you need with `#if Condition1 || Condition2`, it's not a problem anyways. At some point you may be better off just disabling the warning entirely. Warnings about redundancies are too hard when the compiler can't see your entire program at once. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 13 21:42:56 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 13 Jul 2016 21:42:56 -0000 Subject: [GHC] #12389: Limit duplicate export warnings for datatypes In-Reply-To: <045.b9512948fd651abba4c3deecd83cbcfe@haskell.org> References: <045.b9512948fd651abba4c3deecd83cbcfe@haskell.org> Message-ID: <060.12fe3c22913950560d3574f8ea52dfb1@haskell.org> #12389: Limit duplicate export warnings for datatypes -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: Type: feature request | Status: new Priority: normal | Milestone: 8.2.1 Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: #11959 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by dfeuer): Replying to [comment:5 rwbarton]: > Well you don't really want to "silence the warning from duplicate constructors/patterns within the list". You want to silence ''this'' duplicate of `Bar`. If you happen to repeat a different constructor elsewhere in the export list by accident, you'd still want a warning about that. So it would more appropriate to use a mechanism for locally disabling warnings. Local suppression is very heavy for a warning about something as relatively unimportant as this. I'd be happy with a heuristic: accidental duplicates are typically less likely in a constructor/pattern export list than in a (typically much longer) module export list. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 13 21:45:07 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 13 Jul 2016 21:45:07 -0000 Subject: [GHC] #12389: Limit duplicate export warnings for datatypes In-Reply-To: <045.b9512948fd651abba4c3deecd83cbcfe@haskell.org> References: <045.b9512948fd651abba4c3deecd83cbcfe@haskell.org> Message-ID: <060.457b266ac834c2f4b334eda44fd71b25@haskell.org> #12389: Limit duplicate export warnings for datatypes -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: Type: feature request | Status: new Priority: normal | Milestone: 8.2.1 Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: #11959 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by rwbarton): Well I wouldn't be too happy with that; the flag should do what it says on the tin and cater to the needs of normal users over those of CPP-wielding maniacs :) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 13 21:47:28 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 13 Jul 2016 21:47:28 -0000 Subject: [GHC] #12389: Limit duplicate export warnings for datatypes In-Reply-To: <045.b9512948fd651abba4c3deecd83cbcfe@haskell.org> References: <045.b9512948fd651abba4c3deecd83cbcfe@haskell.org> Message-ID: <060.c862cc79f1d65fae0176eeb003c6f019@haskell.org> #12389: Limit duplicate export warnings for datatypes -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: Type: feature request | Status: new Priority: normal | Milestone: 8.2.1 Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: #11959 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by dfeuer): Fine; if I can get leading and trailing commas, I'll be happy. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 14 03:03:33 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 14 Jul 2016 03:03:33 -0000 Subject: [GHC] #3919: Or-patterns as GHC extension In-Reply-To: <051.27f4dc97a096cc6bd656d7691ce3afb5@haskell.org> References: <051.27f4dc97a096cc6bd656d7691ce3afb5@haskell.org> Message-ID: <066.39ccbfb3255b33881391dc43072a3aaf@haskell.org> #3919: Or-patterns as GHC extension -------------------------------------+------------------------------------- Reporter: BjornEdstrom | Owner: Type: feature request | Status: new Priority: normal | Milestone: ⊥ 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): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Iceland_jack): Regarding syntax, could it use data constructor syntax with a magic module {{{#!hs import GHC.OrPatterns ( (:|:) ) -- ( pattern (:|:) ) ? f A = ... f B = ... f unexpected@(C{} :|: D{} :|: E{}) = pprTrace "f" (ppr unexpected) }}} like Edward's suggestion in Records/OverloadedRecordFields/OverloadedLabels {{{#!hs import GHC.ImplicitValues( p, q, area ) }}} ---- {{{#!hs import qualified GHC.OrPatterns as OR ( (:|:) ) f (C{} OR.:|: D{} OR.:|: E{}) = ... }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 14 03:04:19 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 14 Jul 2016 03:04:19 -0000 Subject: [GHC] #12240: Common Sense for Type Classes In-Reply-To: <050.3dcf7ad3ce6a480cdc5fe8435e755275@haskell.org> References: <050.3dcf7ad3ce6a480cdc5fe8435e755275@haskell.org> Message-ID: <065.710f47190646bda7e5cd3da770736c1b@haskell.org> #12240: Common Sense for Type Classes -------------------------------------+------------------------------------- Reporter: Mathnerd314 | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 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 Mathnerd314): > What should the inferred type of g be? My preferred answer is (1). The reasoning is something like: * an untyped function binding... infer a type signature * f creates a constraint, so it's `g :: forall b. C Int b => Int -> b` * it typechecks - done This is distinct from `x = fst f` in the original example. There, `x` is a pattern binding and the monomorphism restriction applies. `x` cannot have a constraint in the inferred type, thus GHC is forced to choose an instance, in particular the `C Int Char` instance, and so the inferred type is `x :: Char`. Similarly, `show (g 2)` generates constraints `Show b, C a b, Num a`, which can either go into the given constraints or be solved, depending on the context. > What your proposal seems to suggest is an alternate way to do defaulting, by consulting the instance environment in question. Defaulting happens in `simpl_top`, while instance resolution happens in `solveSimpleWanteds` in `simpl_loop`. There's a note explaining that defaulting used to be in `simpl_loop`, but doing it outside any implications fixed some programs. I wonder if, analogously, moving instance resolution out near defaulting would result in a similar improvement. It does seem clear that defaulting and top-level instance resolution are intimately entwined with the instance environment. > Specifically, if I have an ambiguous type variable v which occurs in some class C t1 v ..., if there is only ONE choice of v which allows the instance resolution to go through, I should default v to that one! That doesn't sound quite right. For example: {{{#!hs class X a b c instance X [a] (Maybe a) Bool instance X [a] [a] Char x = (\(d :: Dict (X [a] (Maybe Int) b)) -> typeOf d) Dict -- wanted: x = "Dict (X [Int] (Maybe Int) Bool)" }}} I don't see how defaulting would turn `[a]` into `[Int]`, if it did something variable-by-variable. (Also note that defaulting as currently implemented only applies to one- parameter type classes) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 14 03:14:29 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 14 Jul 2016 03:14:29 -0000 Subject: [GHC] #12390: List rules for `Coercible` instances Message-ID: <051.b98e23ec385e9c48fab8abae2b183162@haskell.org> #12390: List rules for `Coercible` instances -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: 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: -------------------------------------+------------------------------------- `:info` on [https://downloads.haskell.org/~ghc/7.8.2/docs/html/libraries/base-4.7.0.0 /Data-Coerce.html#t:Coercible Data.Coerce.Coercible] doesn't display any instances, it's a special class so it should be special-cased {{{ ghci> :i Coercible type role Coercible representational representational class a ~R# b => Coercible (a :: k) (b :: k) -- Defined in ‘GHC.Types’ }}} The base case would be easy to display: {{{#!hs instance Coercible a a -- Generated on the fly }}} but it's trickier to describe the … instance succinctly: {{{#!hs instance Coercible b b' => Coercible (D a b c) (D a b' c') }}} same for newtypes. ---- Maybe it's better to list concrete examples {{{#!hs coerce @(Reader _ _) :: Reader a b -> (a -> Identity b) }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 14 03:22:03 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 14 Jul 2016 03:22:03 -0000 Subject: [GHC] #12390: List rules for `Coercible` instances In-Reply-To: <051.b98e23ec385e9c48fab8abae2b183162@haskell.org> References: <051.b98e23ec385e9c48fab8abae2b183162@haskell.org> Message-ID: <066.4ae405984fb37ba2a7327d89a5156142@haskell.org> #12390: List rules for `Coercible` instances -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: 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): The Coercible class is special in other ways too, there is also [https://phabricator.haskell.org/diffusion/GHC/browse/master/libraries /ghc-prim/GHC/Types.hs;54c95ffcb2cf392df33d2ec397e2301c005ca406$84 no syntax for ~#R] {{{#!hs class a ~R# b => Coercible (a :: k) (b :: k) }}} making it difficult to get more information about `~R#`. (#12023) Some of this might be worth noting in `:info`. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 14 08:02:38 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 14 Jul 2016 08:02:38 -0000 Subject: [GHC] #12382: Rename clashing type variables more consistently In-Reply-To: <046.c5cb956f322074bdfaee0fe12bd9cbb4@haskell.org> References: <046.c5cb956f322074bdfaee0fe12bd9cbb4@haskell.org> Message-ID: <061.a396fd7e4c1670b25869d1cd37670290@haskell.org> #12382: Rename clashing type variables more consistently -------------------------------------+------------------------------------- Reporter: nomeata | Owner: nomeata Type: feature request | Status: patch Priority: low | Milestone: 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:D2402 Wiki Page: | -------------------------------------+------------------------------------- Comment (by Joachim Breitner ): In [changeset:"18ac80ff729eb19ec370ead9f9275b3bc32c1f81/ghc" 18ac80ff/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="18ac80ff729eb19ec370ead9f9275b3bc32c1f81" tidyType: Rename variables of nested forall at once this refactoring commit prepares for fixing #12382, which can now be implemented soley in tidyTyCoVarBndrs. }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 14 09:05:10 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 14 Jul 2016 09:05:10 -0000 Subject: [GHC] #12391: LANGUAGE CPP messes up parsing when backslash like \\ is at end of line (eol) Message-ID: <051.90ff32b6d904c34082d69eb15f9b624a@haskell.org> #12391: LANGUAGE CPP messes up parsing when backslash like \\ is at end of line (eol) -------------------------------------+------------------------------------- Reporter: andreas.abel | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 (Parser) | Keywords: CPP | 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 CPP #-} import Data.List as List main = putStrLn $ "not nice" List.\\ "hot mice" }}} fails with recent ghc (I tried >= 7.8). {{{ Not in scope: ‘List.\’ }}} This problem occurred in a larger context, see https://travis-ci.org/agda/agda/jobs/144514733 It can be traced back to the use of cpp as preprocessor: {{{ $ cpp BackslashAtEOL.hs # 1 "BackslashAtEOL.hs" # 1 "" 1 # 1 "" 3 # 328 "" 3 # 1 "" 1 # 1 "" 2 # 1 "BackslashAtEOL.hs" 2 {-# LANGUAGE CPP #-} import Data.List as List main = putStrLn $ "not nice" List.\ "hot mice" }}} In contrast, cpphs would work correctly here: {{{ $ cpphs BackslashAtEOL.hs #line 1 "BackslashAtEOL.hs" {-# LANGUAGE CPP #-} import Data.List as List main = putStrLn $ "not nice" List.\\ "hot mice" }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 14 09:14:29 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 14 Jul 2016 09:14:29 -0000 Subject: [GHC] #12390: List rules for `Coercible` instances In-Reply-To: <051.b98e23ec385e9c48fab8abae2b183162@haskell.org> References: <051.b98e23ec385e9c48fab8abae2b183162@haskell.org> Message-ID: <066.f9af06edbff2d41548cf97f64682c022@haskell.org> #12390: List rules for `Coercible` instances -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: 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 nomeata): Maybe it would work better if a symbol could have an text field attatched for “arbitrary text to be displayed on `:info`”, and `:info` would show that. It could simply say > Coercible is a special constraint with custom solving rules. Please see section ... of the user’s guide for details. Note that we stopped calling `Coercible` a class; as it is not a class. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 14 09:25:14 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 14 Jul 2016 09:25:14 -0000 Subject: =?utf-8?q?=5BGHC=5D_=2312392=3A_Die_unglaublichen_Effekte_der_?= =?utf-8?b?4oCeUmV2b2x5buKAnC1EacOkdHRhYmxldHRlIQ==?= Message-ID: <045.633367e27ce0c767be617e62a843cd82@haskell.org> #12392: Die unglaublichen Effekte der „Revolyn“-Diättablette! -------------------------------------+------------------------------------- Reporter: Milena | Owner: Type: bug | Status: new Priority: lowest | 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: -------------------------------------+------------------------------------- Seit Januar 2016 erobert ein effektives Diätmittel aus den vereinigten Staaten von Amerika auch die westliche Himmelsphäre! Dabei geht es um ein Abnehmprodukt auf ausschließlich pflanzlicher Grundlage, dass eine extrem fettverbrennende Wirkung besitzt. Erfahrung Revolyn-Diäthelfern: Wir haben die Überraschungs-Pille ausprobiert und herausgefunden, dass die beachtlichen Bestandteile und die Verknüpfung mit dem Ergänzungsprodkut "Pure Cleanse Diät Pillen“ zu unfasbaren Ergebnissen führt. Zwar waren wiranfangs extrem skeptisch, ob die Versprechen der Produkte eingehalten werden, aber die Langzeitwirkung hat mich beeindruckt und parallel fasziniert. Das Team hat zweifellos aber auch neben der Einnahme der Diäthilfen auf die Ernährung acht genommen und Sport getrieben, dies ist zweifellos zu empfehlen! Kombination der beiden Produkte: „Revolyn Diet Tabletten “ und „Pure Cleannse Tabletten“ ergeben zusammen die erstklassige Plattform für eine aussichtsreiche Diät. Während „Revolyn“ die Fettverbrennung gewaltig beschleunigt, erfüllt die „Pure Cleanse Diet Tablette“ andere wichtige Punkte. Es steigert extrem ihre Energie, säubert und entgiftet ihren Organismus und bringt jedermanns Stoffwechsel in Schwung! Es verhindert also die normalen side-effects einer Diät: das Trägheitsgefühl, die 0-Bock-Phase und die Schmerzen in der Bauchgegend. Inhaltsstoffe von Revolyn-Tabletten: Doch wie ist dies alles möglich? Gucken wir uns den Inhalt mal im Einzelnen an. Die Revolyn Diät-Tablette enthält gleich mehrere natürliche und effektive Bestandteile. Der grüne Tee und die enthaltenen Guarana- Bestandteile verbessern gehörig den Metabolismus. Außerdem steigert Guarana den Blutdruck und aus dem Grund auch die Anzahl an verbrannten Kalorien.Der Inhaltsstoff „Damiana“ sichert eine leistungsfähigere Libido, steigert die Fettverbrennung und stärkt das Nerven- und Immunsystem! Ein echtes Allround-Talent!Das außerdem enthaltene Granatapfel-Extrakt wirkt positiv auf die Blutfette (beschleunigt dessen Vernichtung) und beinhaltet extrem viele gute und für die Gesundheit wichtige Vitamine. Einnahme von den Revolyn-Diätpillen: Das Einnehmen von [http://www.abnehmprodukte-test.com Revolyn Diet] Pillen ist mega einfach erklärt. Am Morgen und Am Abend eine Pille mit einem Glas mit zuckerfreier Sprudel einnehmen – und voilà. Das Einnehmen von „Pure Life Cleanse ist noch problemloser und benutzerfreundlicher: Eine Tablette am frühen Nachmittag mit einem Schluck mit zuckerfreier Sprudel zu sich nehmen, voila! Wie teuer sind die Revolyn-Diätpillen? Gegen anderen Abnehmprodukten mit einer sich ähnelnden Wirkung „ist Revolyn “ und „die [http://www.abnehmprodukte-test.com/revolyn-diat-und- pure-cleanse Pure Cleanse] Diet Pillen“ ist Revolyn sehr kostengünstig. Zwar kostet 1 Flasche 39,95 €, allerdings verringert sich der Einzelpreis je nach Menge an bestellten Produkten. Wer 2 Flaschen bestellt (79,95Euro) erhält eine einfach so obendrauf. Vier Flaschen kosten 159,80 Taler, es gibt aber auch vier Flaschen für lau dazu. Im Endeffekt bekommt ihr also 8 Flaschen für nur 159,80 €! Ein einzigartiger Oberknaller! -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 14 09:43:32 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 14 Jul 2016 09:43:32 -0000 Subject: [GHC] #12170: Add flag to control whether out of scope variables should be deferred with -fdefer-typed-holes In-Reply-To: <049.73087dc6a5aa1aa799f9994d0d1022ff@haskell.org> References: <049.73087dc6a5aa1aa799f9994d0d1022ff@haskell.org> Message-ID: <064.a9ebb250f629ee81b110f82141fbdb9d@haskell.org> #12170: Add flag to control whether out of scope variables should be deferred with -fdefer-typed-holes -------------------------------------+------------------------------------- Reporter: mpickering | Owner: 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: #10569, #12156 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by shahn): * cc: shahn (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 14 13:18:45 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 14 Jul 2016 13:18:45 -0000 Subject: [GHC] #12390: List rules for `Coercible` instances In-Reply-To: <051.b98e23ec385e9c48fab8abae2b183162@haskell.org> References: <051.b98e23ec385e9c48fab8abae2b183162@haskell.org> Message-ID: <066.e392b7eb90bf6bfca5a1e77ca78fce9d@haskell.org> #12390: List rules for `Coercible` instances -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: 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): +1 to comment:2. `Coercible` is not a class. Any resemblance it has to a class is purely historical. That said, I'm very sympathetic to the original motivation of having `:info Coercible` print something more useful. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 14 14:04:00 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 14 Jul 2016 14:04:00 -0000 Subject: [GHC] #12393: Poor error message with equational type constraints Message-ID: <044.ac4c165f085adec9731a3cd7a651c47e@haskell.org> #12393: Poor error message with equational type constraints --------------------------------------+--------------------------------- Reporter: laneb | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 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: --------------------------------------+--------------------------------- GHCi 8.0.1 is giving a poor error message when it can't derive a typeclass when there's an equational type constraint involved. A simple example: {{{#!hs {-# LANGUAGE TypeFamilies #-} class Foo a where type FooInner a fromInner :: FooInner a -> a newtype Bar = Bar { fromBar::Char } deriving (Show) instance Foo Bar where type FooInner Bar = Char fromInner = Bar myFunc :: (Foo foo, FooInner foo ~ Char) => String -> foo myFunc = fromInner . head }}} Many things work as expected: {{{ ghc> :t myFunc myFunc :: (FooInner foo ~ Char, Foo foo) => String -> foo ghc> :t (myFunc "z") (myFunc "z") :: (FooInner foo ~ Char, Foo foo) => foo ghc> (myFunc "z") :: Bar Bar {fromBar = 'z'} }}} but if I just evaluate the function without the typecast I get an error: {{{ ghc> myFunc "z" :486:1: error: • Illegal equational constraint FooInner foo ~ Char (Use GADTs or TypeFamilies to permit this) • When checking the inferred type it :: forall foo. (FooInner foo ~ Char, Foo foo) => foo }}} Now, there should certainly be an error here: GHC doesn't know the exact type of {{{myFunc}}} so it can't check if it's an instance of {{{Show}}}. However, unless I'm not understanding what's going on, the error should be something like "Could not deduce Show", not "Illegal equational constraint". Even if that __is__ what's going on, the suggestion to "Use GADTs or TypeFamilies to permit this" is clearly wrong, as I am already using {{{TypeFamilies}}}. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 14 14:32:53 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 14 Jul 2016 14:32:53 -0000 Subject: [GHC] #12394: broken (obsolete?) links to user guide Message-ID: <049.236b514a0a8df239b8fccae12a734bcb@haskell.org> #12394: broken (obsolete?) links to user guide -------------------------------------+------------------------------------- Reporter: j.waldmann | Owner: 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: -------------------------------------+------------------------------------- A lot of place (Haskell Wiki, etc., example: bottom of https://wiki.haskell.org/Language_Pragmas) have links like this https://downloads.haskell.org/~ghc/latest/docs/html/users_guide/ghc- language-features.html which gives 404 now. Is there a systematic way of redirecting this? It seems not, because actual names did change, the correct link should now be https://downloads.haskell.org/~ghc/latest/docs/html/users_guide/lang.html The old name (URL) was just the section heading? Which seemed reasonable. The new one just looks like a file name. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 14 16:20:10 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 14 Jul 2016 16:20:10 -0000 Subject: [GHC] #12389: Limit duplicate export warnings for datatypes In-Reply-To: <045.b9512948fd651abba4c3deecd83cbcfe@haskell.org> References: <045.b9512948fd651abba4c3deecd83cbcfe@haskell.org> Message-ID: <060.cccc82c3a767d882f0cb042f1c0043de@haskell.org> #12389: Limit duplicate export warnings for datatypes -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: Type: feature request | Status: new Priority: normal | Milestone: 8.2.1 Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: #11959 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): If I remember right, the export list itself does allow extra commas. So it seems a bit inconsistent not to allow the same story for the `Foo( P1, P2 )` form. So this would be ok with me. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 14 16:57:17 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 14 Jul 2016 16:57:17 -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.ab1a76a7825f08e42e3a945d9953b5f7@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): Lambda motivation {{{#!hs -- phoas :: Phoas v (x -> y -> x) -- phoas = PLam (\x -> PLam (\y -> PVar x)) phoas :: Phoas v (x -> y -> x) phoas = PLam \x -> PLam \y -> PVar x }}} {{{#!hs -- ex = λ (\x -> λ (\y -> x)) ex = λ \x -> λ \y -> x }}} Would this parse? {{{#!hs ex = λ\ x -> λ\ y -> x }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 14 17:03:05 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 14 Jul 2016 17:03:05 -0000 Subject: [GHC] #393: functions without implementations In-Reply-To: <047.8e9c859b4db83c0d687094f53af0d886@haskell.org> References: <047.8e9c859b4db83c0d687094f53af0d886@haskell.org> Message-ID: <062.ad87048faefe609c11db2282090d1b6a@haskell.org> #393: functions without implementations -------------------------------------+------------------------------------- Reporter: c_maeder | Owner: Type: feature request | Status: new Priority: normal | Milestone: ⊥ Component: Compiler (Type | Version: None checker) | 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): Should also work for methods. This currently fails: {{{#!hs class FFunctor p where ffmap :: (forall x. f x -> g x) -> (p f -> p g) instance FFunctor (TList l) where ffmap :: (forall x. f x -> g x) -> (TList l f -> TList l g) ffmap = undefined }}} I would like {{{#!hs class FFunctor p where ffmap :: (forall x. f x -> g x) -> (p f -> p g) instance FFunctor (TList l) where ffmap :: (forall x. f x -> g x) -> (TList l f -> TList l g) }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 14 18:38:33 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 14 Jul 2016 18:38:33 -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.ba6164515e2eb37cadcbfe9774d11878@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 maeder): Replying to [comment:32 Iceland_jack]: [...] > -- ex = λ (\x -> λ (\y -> x)) > > ex = λ \x -> λ \y -> x > }}} > > Would this parse? > > {{{#!hs > ex = λ\ x -> λ\ y -> x > }}} Surely, this is a lexical issue. No space is needed between symbols (like "\") and (unicode) letters (like x, y, or λ), although I recommend to always leave a space, i.e. "f λ\ ..." would be parsed as "(f λ)\ ...". -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 14 19:13:35 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 14 Jul 2016 19:13:35 -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.a03e02e98ed96ccc7cef0a0aed0c75c5@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): Replying to [comment:33 maeder]: > Replying to [comment:32 Iceland_jack]: > Surely, this is a lexical issue. No space is needed between symbols (like "\") and (unicode) letters (like x, y, or λ), although I recommend to always leave a space, i.e. "f λ\ ..." would be parsed as "(f λ)\ ...". I was wondering if we could mimic the upper-case lambda `Λ` by using a lower-case `l` for lambda {{{#!hs ex' = l\ x -> l\ y -> x }}} `l\` look like a malformed lambda! (don't) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 14 19:58:18 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 14 Jul 2016 19:58:18 -0000 Subject: [GHC] #12395: Misleading GHCi errors when package is installed Message-ID: <047.ba2be8af6e35ce15a9e6f8ef5ab4b38f@haskell.org> #12395: Misleading GHCi errors when package is installed -------------------------------------+------------------------------------- Reporter: crockeea | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: GHCi | Version: 8.0.1 Keywords: | 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: -------------------------------------+------------------------------------- When a package is installed in a cabal sandbox/global package directory and code is loaded with GHCi when a file has been deleted, GHCi gives very misleading errors. First, if we don't install the package, we get the correct error/expected result: {{{ > mv B.hs B.hs.old > ghci Main.hs Main.hs:3:1: error: Failed to load interface for ‘B’ Use -v to see a list of the files searched for. Failed, modules loaded: A. }}} But if we first install the package, we get a very strange error: {{{ > mv B.hs.old B.hs > cabal install > mv B.hs B.hs.old > ghci Main.hs Main.hs:6:14: error: Ambiguous occurrence ‘str’ It could refer to either ‘A.str’, imported from ‘A’ at Main.hs:2:1-8 (and originally defined at A.hs:7:1-3) or ‘B.str’, imported from ‘B’ at Main.hs:3:1-8 (and originally defined in ‘A’) Failed, modules loaded: A. }}} I'm using GHC 8.0.1, cabal-install-1.24.0.0, and Cabal Library-1.24.0.0. This is Very Annoying because I use this process to minimize examples. For example, when I want to simplify code by removing a module, I just delete it and then rely on GHCi to tell me what I need to update. Anyone not aware of this bug would be totally confused by the error, and even though I do know about the bug, the error is completely unhelpful. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 14 19:58:53 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 14 Jul 2016 19:58:53 -0000 Subject: [GHC] #12395: Misleading GHCi errors when package is installed In-Reply-To: <047.ba2be8af6e35ce15a9e6f8ef5ab4b38f@haskell.org> References: <047.ba2be8af6e35ce15a9e6f8ef5ab4b38f@haskell.org> Message-ID: <062.42506998e723ee2b3c146d009d0c11ab@haskell.org> #12395: Misleading GHCi errors when package is installed -------------------------------------+------------------------------------- Reporter: crockeea | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: GHCi | Version: 8.0.1 Resolution: | Keywords: 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 crockeea): * Attachment "test2.tar" added. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 14 20:25:18 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 14 Jul 2016 20:25:18 -0000 Subject: [GHC] #7662: Improve GC of mutable objects In-Reply-To: <045.1df59d879ca14d9200a5a4cc6e9474e1@haskell.org> References: <045.1df59d879ca14d9200a5a4cc6e9474e1@haskell.org> Message-ID: <060.3828f1ae3fc94735a90780694f5f16f9@haskell.org> #7662: Improve GC of mutable objects -------------------------------------+------------------------------------- Reporter: ezyang | Owner: Type: feature request | Status: new Priority: normal | Milestone: ⊥ Component: Runtime System | Version: 7.7 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 dobenour): MLton does manage to unpack refs in records though. I think that it can be done in general IF you either: - support interior pointers in the GC (which GHC probably doesn't). - represent mutable refs as "fat pointers", consisting of both a pointer to the object being mutated and a pointer to the cell within the object. In this case {{{#!hs data SomeType = SomeType { x :: {-# UNPACK #-} !(IORef Int) , y :: {-# UNPACK #-} !Char } getRef :: SomeType -> IORef Int getRef = x }}} `x (v :: SomeType)` would produce an object that contains a pointer to `v` (for the GC) and a pointer to field `x` of `v` (used to mutate `x`). -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 14 20:49:30 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 14 Jul 2016 20:49:30 -0000 Subject: [GHC] #7662: Improve GC of mutable objects In-Reply-To: <045.1df59d879ca14d9200a5a4cc6e9474e1@haskell.org> References: <045.1df59d879ca14d9200a5a4cc6e9474e1@haskell.org> Message-ID: <060.5198190ce29309fd8347b5d717ae15db@haskell.org> #7662: Improve GC of mutable objects -------------------------------------+------------------------------------- Reporter: ezyang | Owner: Type: feature request | Status: new Priority: normal | Milestone: ⊥ Component: Runtime System | Version: 7.7 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 rwbarton): I think this has been discussed elsewhere too, but I don't understand how the above could be consistent with Haskell's semantics. What if I define {{{#!hs upperize :: SomeType -> SomeType upperize s = s { y = toUpper (y s) } }}} Obviously this needs to allocate a new `SomeType` closure on the heap, but if the `IORef Int` is completely unpacked into a mutable field of `SomeType` closures, then the new closure can't share `x` with the old closure. In general just constructing a `SomeType` value would have the observable effect of creating a new mutable cell and so would have to live in IO. In short, ML's records with mutable fields have identity, and so are quite different than just sticking an `IORef` inside a record in Haskell. In Haskell the `IORef` itself has identity (and thus is created and accessed through IO actions) but the record `SomeType` does not. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 14 21:12:48 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 14 Jul 2016 21:12:48 -0000 Subject: [GHC] #12393: Poor error message with equational type constraints In-Reply-To: <044.ac4c165f085adec9731a3cd7a651c47e@haskell.org> References: <044.ac4c165f085adec9731a3cd7a651c47e@haskell.org> Message-ID: <059.0b6873311ce0c84e712339774a6fe100@haskell.org> #12393: Poor error message with equational type constraints ---------------------------------+-------------------------------------- Reporter: laneb | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 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 rwbarton): > Even if that is what's going on, the suggestion to "Use GADTs or TypeFamilies to permit this" is clearly wrong, as I am already using TypeFamilies. Actually, it's technically not wrong: you don't have TypeFamilies turned on ''in GHCi'' which is where the problematic constraint arose. But I certainly agree that GHC should just give the ambiguous type variable error in preference to the one it gave you, and probably shouldn't bother checking the inferred type of `it` at all. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 14 21:15:44 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 14 Jul 2016 21:15:44 -0000 Subject: [GHC] #12393: Poor error message with equational type constraints In-Reply-To: <044.ac4c165f085adec9731a3cd7a651c47e@haskell.org> References: <044.ac4c165f085adec9731a3cd7a651c47e@haskell.org> Message-ID: <059.b7dfddd7a0746c3988bc93eefd46b428@haskell.org> #12393: Poor error message with equational type constraints ---------------------------------+-------------------------------------- Reporter: laneb | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 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 rwbarton): Also note that there is another ticket somewhere about having flags set in the current module be in effect in ghci also, which would address this case too. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 14 22:16:20 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 14 Jul 2016 22:16:20 -0000 Subject: [GHC] #12057: TypeFamilyDependencies on Data.Type.Bool's `Not` In-Reply-To: <051.38c482983531342047bddb8add84ef15@haskell.org> References: <051.38c482983531342047bddb8add84ef15@haskell.org> Message-ID: <066.1a88df6058104a198045456e21cebc3c@haskell.org> #12057: TypeFamilyDependencies on Data.Type.Bool's `Not` -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Iceland_jack Type: feature request | Status: new Priority: normal | Milestone: Component: libraries/base | Version: 8.0.1 Resolution: | Keywords: TypeFamilies, | Injective, newcomer Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2268 Wiki Page: | -------------------------------------+------------------------------------- Comment (by Ryan Scott ): In [changeset:"37aeff631766eebf5820b980d614bef78960291a/ghc" 37aeff63/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="37aeff631766eebf5820b980d614bef78960291a" Added type family dependency to Data.Type.Bool.Not Summary: Signed-off-by: Baldur Blöndal Reviewers: goldfire, RyanGlScott, austin, bgamari, hvr Reviewed By: RyanGlScott, austin Subscribers: RyanGlScott, thomie Differential Revision: https://phabricator.haskell.org/D2268 GHC Trac Issues: #12057 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 14 22:17:39 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 14 Jul 2016 22:17:39 -0000 Subject: [GHC] #12057: TypeFamilyDependencies on Data.Type.Bool's `Not` In-Reply-To: <051.38c482983531342047bddb8add84ef15@haskell.org> References: <051.38c482983531342047bddb8add84ef15@haskell.org> Message-ID: <066.09d038765037e71d1ad8e54f0f50a468@haskell.org> #12057: TypeFamilyDependencies on Data.Type.Bool's `Not` -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Iceland_jack Type: feature request | Status: closed Priority: normal | Milestone: 8.2.1 Component: libraries/base | Version: 8.0.1 Resolution: fixed | Keywords: TypeFamilies, | Injective, newcomer Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2268 Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * status: new => closed * resolution: => fixed * milestone: => 8.2.1 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 14 22:38:20 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 14 Jul 2016 22:38:20 -0000 Subject: [GHC] #12396: Panic when specializing in another module Message-ID: <047.cfbab0d2aaad50ebf39c103bee8948e0@haskell.org> #12396: Panic when specializing in another module -------------------------------------+------------------------------------- Reporter: crockeea | Owner: 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 Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- In the attached example (which requires `criterion` and `deepseq`), when compiled with `ghc -O2 -funfolding-use-threshold1000 Main.hs`, I get the following error on `Main.hs`: {{{ ghc: panic! (the 'impossible' happened) (GHC version 8.0.1 for x86_64-unknown-linux): StgCmmEnv: variable not found $d(%,%)_aaTF local binds for: $trModule $sfool $trModule1 $trModule2 $wlvl_rgY8 lvl_rgY9 lvl1_rgYa lvl3_rgYc lvl4_rgYd lvl5_rgYe lvl6_rgYf lvl7_rgYg lvl8_rgYh lvl9_rgYi lvl10_rgYj lvl11_rgYk lvl12_rgYl lvl13_rgYm lvl14_rgYn lvl15_rgYo lvl16_rgYp lvl17_rgYq lvl18_rgYr lvl19_rgYs lvl20_rgYt lvl21_rgYu lvl22_rgYv lvl23_rgYw lvl24_rgYx lvl25_rgYy lvl26_rgYz lvl27_rgYA lvl28_rgYB lvl29_rgYC lvl30_rgYD lvl31_rgYE lvl32_rgYF lvl33_rgYG lvl34_rgYH lvl35_rgYI lvl36_rgYJ lvl37_rgYK lvl38_rgYL lvl39_rgYM lvl40_rgYN lvl41_rgYO lvl42_rgYP lvl43_rgYQ lvl44_rgYR lvl45_rgYS lvl46_rgYT lvl47_rgYU lvl48_rgYV lvl49_rgYW lvl50_rgYX lvl51_rgYY lvl52_rgYZ lvl53_rgZ0 lvl54_rgZ1 lvl55_rgZ2 lvl56_rgZ3 lvl57_rgZ4 lvl58_rgZ5 lvl59_rgZ6 lvl60_rgZ7 lvl61_rgZ8 lvl62_rgZ9 lvl63_rgZa lvl64_rgZb lvl65_rgZc lvl66_rgZd ww1_rgZe ww2_rgZf ww3_rgZg ww4_rgZh pinfo_rgZi pinfo1_rgZj pinfo2_rgZk pinfo3_rgZl lvl67_rgZm lvl68_rgZn lvl69_rgZo $wgo12_rgZp eta_sh1k wild_sh1l v_sh1m sat_sh1n }}} I initially found this bug when I added a `SPECIALIZE` pragma for `fool` in `Main.hs`. However, I need `funfolding-use-threshold1000` and the constraint synonym `UCRTElt` in `Foo.hs` to trigger the bug. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 14 22:38:39 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 14 Jul 2016 22:38:39 -0000 Subject: [GHC] #12396: Panic when specializing in another module In-Reply-To: <047.cfbab0d2aaad50ebf39c103bee8948e0@haskell.org> References: <047.cfbab0d2aaad50ebf39c103bee8948e0@haskell.org> Message-ID: <062.e3df44542a1777f24eeb61d6d27da69e@haskell.org> #12396: Panic when specializing in another module -------------------------------------+------------------------------------- Reporter: crockeea | Owner: 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 | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by crockeea): * Attachment "12396.tar" added. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 14 22:39:45 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 14 Jul 2016 22:39:45 -0000 Subject: [GHC] #12396: Panic when specializing in another module In-Reply-To: <047.cfbab0d2aaad50ebf39c103bee8948e0@haskell.org> References: <047.cfbab0d2aaad50ebf39c103bee8948e0@haskell.org> Message-ID: <062.358566be64e2355809808914ab90a51a@haskell.org> #12396: Panic when specializing in another module -------------------------------------+------------------------------------- Reporter: crockeea | Owner: 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 | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Description changed by crockeea: @@ -102,1 +102,3 @@ - constraint synonym `UCRTElt` in `Foo.hs` to trigger the bug. + constraint synonym `UCRTElt` in `Foo.hs` to trigger the bug. Every time I + tried to remove `criterion`, the bug stopped triggering, though I + seriously doubt that the bug is in `criterion`. New description: In the attached example (which requires `criterion` and `deepseq`), when compiled with `ghc -O2 -funfolding-use-threshold1000 Main.hs`, I get the following error on `Main.hs`: {{{ ghc: panic! (the 'impossible' happened) (GHC version 8.0.1 for x86_64-unknown-linux): StgCmmEnv: variable not found $d(%,%)_aaTF local binds for: $trModule $sfool $trModule1 $trModule2 $wlvl_rgY8 lvl_rgY9 lvl1_rgYa lvl3_rgYc lvl4_rgYd lvl5_rgYe lvl6_rgYf lvl7_rgYg lvl8_rgYh lvl9_rgYi lvl10_rgYj lvl11_rgYk lvl12_rgYl lvl13_rgYm lvl14_rgYn lvl15_rgYo lvl16_rgYp lvl17_rgYq lvl18_rgYr lvl19_rgYs lvl20_rgYt lvl21_rgYu lvl22_rgYv lvl23_rgYw lvl24_rgYx lvl25_rgYy lvl26_rgYz lvl27_rgYA lvl28_rgYB lvl29_rgYC lvl30_rgYD lvl31_rgYE lvl32_rgYF lvl33_rgYG lvl34_rgYH lvl35_rgYI lvl36_rgYJ lvl37_rgYK lvl38_rgYL lvl39_rgYM lvl40_rgYN lvl41_rgYO lvl42_rgYP lvl43_rgYQ lvl44_rgYR lvl45_rgYS lvl46_rgYT lvl47_rgYU lvl48_rgYV lvl49_rgYW lvl50_rgYX lvl51_rgYY lvl52_rgYZ lvl53_rgZ0 lvl54_rgZ1 lvl55_rgZ2 lvl56_rgZ3 lvl57_rgZ4 lvl58_rgZ5 lvl59_rgZ6 lvl60_rgZ7 lvl61_rgZ8 lvl62_rgZ9 lvl63_rgZa lvl64_rgZb lvl65_rgZc lvl66_rgZd ww1_rgZe ww2_rgZf ww3_rgZg ww4_rgZh pinfo_rgZi pinfo1_rgZj pinfo2_rgZk pinfo3_rgZl lvl67_rgZm lvl68_rgZn lvl69_rgZo $wgo12_rgZp eta_sh1k wild_sh1l v_sh1m sat_sh1n }}} I initially found this bug when I added a `SPECIALIZE` pragma for `fool` in `Main.hs`. However, I need `funfolding-use-threshold1000` and the constraint synonym `UCRTElt` in `Foo.hs` to trigger the bug. Every time I tried to remove `criterion`, the bug stopped triggering, though I seriously doubt that the bug is in `criterion`. -- -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 15 00:08:24 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 15 Jul 2016 00:08:24 -0000 Subject: [GHC] #12076: "lazy" leads to undefined reference to `stg_ap_0_upd_info' In-Reply-To: <045.45bfd5a6dee62b13780515de863d4289@haskell.org> References: <045.45bfd5a6dee62b13780515de863d4289@haskell.org> Message-ID: <060.e431af2e7f0999dcc78d89b1d56ecbb0@haskell.org> #12076: "lazy" leads to undefined reference to `stg_ap_0_upd_info' -------------------------------------+------------------------------------- Reporter: ezyang | Owner: ezyang Type: bug | Status: merge Priority: high | Milestone: 8.0.2 Component: Compiler | Version: 8.0.1-rc2 (CodeGen) | 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:D2309 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * priority: normal => high Comment: This actually seems to affect a number of packages (e.g. `servant- server`), especially when built with `-O0`. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 15 00:23:06 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 15 Jul 2016 00:23:06 -0000 Subject: [GHC] #12113: ghc-8.0.1-rc4: unification false positive? In-Reply-To: <048.c95bd6fbcccb5a650cdc8ab8ee561a4e@haskell.org> References: <048.c95bd6fbcccb5a650cdc8ab8ee561a4e@haskell.org> Message-ID: <063.5cb20463e445181f55fe45fc94d0d895@haskell.org> #12113: ghc-8.0.1-rc4: unification false positive? -------------------------------------+------------------------------------- Reporter: _deepfire | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1-rc4 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC accepts | Unknown/Multiple invalid program | Test Case: Yes. Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by _deepfire): * cc: Richard, Eisenberg, (added) Comment: Cc: @goldfire -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 15 00:29:19 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 15 Jul 2016 00:29:19 -0000 Subject: [GHC] #12113: ghc-8.0.1-rc4: unification false positive? In-Reply-To: <048.c95bd6fbcccb5a650cdc8ab8ee561a4e@haskell.org> References: <048.c95bd6fbcccb5a650cdc8ab8ee561a4e@haskell.org> Message-ID: <063.d10d617e8ffc6b03615a5319dd137da3@haskell.org> #12113: ghc-8.0.1-rc4: unification false positive? -------------------------------------+------------------------------------- Reporter: _deepfire | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1-rc4 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC accepts | Unknown/Multiple invalid program | Test Case: Yes. Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by _deepfire): * cc: Richard, Eisenberg, (removed) * cc: eir@… (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 15 03:59:16 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 15 Jul 2016 03:59:16 -0000 Subject: [GHC] #12088: Promote data family instance constructors In-Reply-To: <048.155fdb7e7ce6e09c92258c376a6950ab@haskell.org> References: <048.155fdb7e7ce6e09c92258c376a6950ab@haskell.org> Message-ID: <063.f7eb5b6d820f6298bf9a9224bf1fa4dd@haskell.org> #12088: Promote data family instance constructors -------------------------------------+------------------------------------- Reporter: alexvieth | Owner: Type: feature request | Status: new Priority: normal | Milestone: 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 | Differential Rev(s): Phab:D2272 Wiki Page: | -------------------------------------+------------------------------------- Comment (by alexvieth): I've spent some more time studying this and now I'm even more convinced that we should stay with my solution. Take a look at these modules: {{{#!hs -- A.hs {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE KindSignatures #-} {-# LANGUAGE UndecidableInstances #-} module A where import Data.Kind type family Closed (t :: Type) :: Type where Closed t = Open t type family Open (t :: Type) :: Type }}} {{{#!hs -- B.hs {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE TypeInType #-} {-# LANGUAGE DataKinds #-} {-# LANGUAGE KindSignatures #-} {-# LANGUAGE GADTs #-} module B where import Data.Kind import A data Q data family F (t :: Type) :: Closed t -> Type type instance Open Q = Bool data instance F Q r where F0 :: F Q 'True }}} The point is that `type instance Open Q` must be checked before `data instance F Q r`, even though we can't see this dependency, as it's hidden in `A.hs`. With Simon's suggestion, dependency analysis of B gives `[data Q, data family F, type instance Open Q, data instance F Q r]` and then it's reordered to get `[data Q, type instance Open Q, data family F, data instance F Q r]` (insert `type instance Open Q` as early as possible, then do the same for `data instance F Q r`). It's all good! But if we change the order of the definitions in the source file, we get a different result! {{{#!hs -- B.hs {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE TypeInType #-} {-# LANGUAGE DataKinds #-} {-# LANGUAGE KindSignatures #-} {-# LANGUAGE GADTs #-} module B where import Data.Kind import A data family F (t :: Type) :: Closed t -> Type data Q type instance Open Q = Bool data instance F Q r where F0 :: F Q 'True }}} Here we get `[data family F t, data Q, type instance Open Q, data instance F Q r]`, and then we reorder it to `[data family F t, data Q, type instance F Q r, type instance Open Q]` (first put `type instance Open Q` as soon as possible, then put `data instance F Q r` as soon as possible, which is right after `data Q`). Checking `type instance F Q r` causes a failure because we don't have `type instance Open Q` yet. The issue: this algorithm doesn't discover that `type instance Open Q` can go before `data family F t`. Whether it fails as above depends upon the order in which we choose to merge instance declarations into the `TyClDecl` list, but in any case there will be a way to make it fail based on the order of declarations. Taking some `TyClDecl` order and then inserting the `InstDecl`s without ever re-ordering the `TyClDecl`s will not work. A more complicated algorithm is needed. The one I've implemented doesn't have this problem, thanks to the artificial dependency of `data family F t` on `type instance Open Q`. I should also add that I don't think `TyClGroup` should be changed to have only singleton `InstDecl` groups. I'd say it's good that this type represents the actual dependency structure, regardless of whether it's valid according to the type checker. We'll let the type checker programs determine that after the groups are made, but having the renamer do this would be overextending the responsibilities of the renamer. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 15 10:46:42 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 15 Jul 2016 10:46:42 -0000 Subject: [GHC] #11427: superclasses aren't considered because context is no smaller than the instance head In-Reply-To: <045.5bbd322743d829f91b935ee5364b27b3@haskell.org> References: <045.5bbd322743d829f91b935ee5364b27b3@haskell.org> Message-ID: <060.c860b74f0ade3247d408673c653e3866@haskell.org> #11427: superclasses aren't considered because context is no smaller than the instance head -------------------------------------+------------------------------------- Reporter: phadej | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1-rc1 Resolution: | Keywords: 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 Blaisorblade): Possibly silly question: the extra expressivity here is behind a language flag, so why does its support reduce the normal language? Is the extra check (for non-bottomness) needed without recursive superclasses? - Is it hard to reproduce the old behavior with the new algorithm? - Or is it a bad idea, because then the examples in this bug would work normally and break with UndecidableSuperClasses? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 15 15:17:26 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 15 Jul 2016 15:17:26 -0000 Subject: [GHC] #12397: Support for PDB debug information generation Message-ID: <045.7bf08882b414350a48568f9ca1e85e23@haskell.org> #12397: Support for PDB debug information generation -------------------------------------+------------------------------------- Reporter: varosi | Owner: Type: feature | Status: new request | Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 (Debugging) | Keywords: | Operating System: Windows Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- It would be great if GHC support PDB files for debugging. This will help in Windows debugging and it will gain more stronger positions on Windows platform. Here I found format description. I'm not sure if it is similar to DWARF so it could be easily generated from existing DWARF implementation. https://github.com/Microsoft/microsoft-pdb -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 15 15:18:41 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 15 Jul 2016 15:18:41 -0000 Subject: [GHC] #12397: Support for PDB debug information generation In-Reply-To: <045.7bf08882b414350a48568f9ca1e85e23@haskell.org> References: <045.7bf08882b414350a48568f9ca1e85e23@haskell.org> Message-ID: <060.2932a34bc63f2d71e649973419c9dc44@haskell.org> #12397: Support for PDB debug information generation -------------------------------------+------------------------------------- Reporter: varosi | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 (Debugging) | 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: | -------------------------------------+------------------------------------- Description changed by varosi: @@ -3,1 +3,2 @@ - platform. + platform. There are great Windows tools for profiling and debugging that + are sitting on PDB files. New description: It would be great if GHC support PDB files for debugging. This will help in Windows debugging and it will gain more stronger positions on Windows platform. There are great Windows tools for profiling and debugging that are sitting on PDB files. Here I found format description. I'm not sure if it is similar to DWARF so it could be easily generated from existing DWARF implementation. https://github.com/Microsoft/microsoft-pdb -- -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 15 18:59:05 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 15 Jul 2016 18:59:05 -0000 Subject: [GHC] #12398: Expose 'withCleanupSession' as a replacement for 'defaultCleanupHandler' Message-ID: <046.ae05c9ccdd84834d5d2d4568141d97f7@haskell.org> #12398: Expose 'withCleanupSession' as a replacement for 'defaultCleanupHandler' -------------------------------------+------------------------------------- Reporter: DanielG | Owner: 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: -------------------------------------+------------------------------------- GHC used to export 'defaultCleanupHandler' going back as far as 7.4, starting with 8.0 no equivalent function seems to be exported. Please consider exporting 'withCleanupSession' as a replacement. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 15 19:03:00 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 15 Jul 2016 19:03:00 -0000 Subject: [GHC] #12398: Expose 'withCleanupSession' as a replacement for 'defaultCleanupHandler' In-Reply-To: <046.ae05c9ccdd84834d5d2d4568141d97f7@haskell.org> References: <046.ae05c9ccdd84834d5d2d4568141d97f7@haskell.org> Message-ID: <061.a3e2849c5dd34368f0a7b12b1169ecfa@haskell.org> #12398: Expose 'withCleanupSession' as a replacement for 'defaultCleanupHandler' -------------------------------------+------------------------------------- Reporter: DanielG | Owner: 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 DanielG): I should also note that using runGhc/runGhcT is not fesible as they mess with signal handlers which is undesirable for what I'm doing. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 15 21:26:11 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 15 Jul 2016 21:26:11 -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.207286852d9397c51843d3daa070532a@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): The recent [https://github.com/koengit/KeyMonad/blob/9bcf22d3f5fb08ff0bfb6b6db7c179d8675df520/paper.lhs ''Key'' monad] lets us mimic Arrow notation in user code {{{#!hs -- addA :: Arrow a => a b Int -> a b Int -> a b Int -- addA f g = proc $ \z -> do -- x <- f -< z -- y <- g -< z -- return $ (+) <$> x <*> y addA :: Arrow a => a b Int -> a b Int -> a b Int addA f g = proc \z -> do x <- f -< z y <- g -< z return $ (+) <$> x <*> y }}} compared to {{{#!hs addA :: Arrow a => a b Int -> a b Int -> a b Int addA f g = procb z -> do x <- f -< z y <- g -< z returnA -< x + y }}} ---- In an alternative universe with idiom brackets {{{#!hs addA :: Arrow a => a b Int -> a b Int -> a b Int addA f g = proc \z -> do x <- f -< z y <- g -< z return [| x + y |] }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 15 22:15:17 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 15 Jul 2016 22:15:17 -0000 Subject: [GHC] #12397: Support for PDB debug information generation In-Reply-To: <045.7bf08882b414350a48568f9ca1e85e23@haskell.org> References: <045.7bf08882b414350a48568f9ca1e85e23@haskell.org> Message-ID: <060.450e0668a241279a759c39c6ef8d1129@haskell.org> #12397: Support for PDB debug information generation -------------------------------------+------------------------------------- Reporter: varosi | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 (Debugging) | 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 Phyx-): I'm very keen on this myself, but last time I looked at this the repository wasn't in a very usable state. The repository basically contains the structures definition and it seems they added the streams implementation now to. But the bulk of the code is in Mscorpdb.dll which is proprietary and we can't redistribute it. So the situation is kind of hard until someone implements an open source variant of that (Since I think GHC has too many Linux/Mac only developers to foster such a project for the Windows world, and maintain it). Currently I believe libDWARF is used for DWARF support. I'm hoping for Microsoft to either release the code for Mscorpdb.dll or change the licensing.. Alternatively, we could use tools that convert from DWARF to PDB as a post-build step, such as https://github.com/rainers/cv2pdb . But yeah Ideally we would be able to generate it ourselves. I have been thinking about trying to use the code for that tool and internally do a DWARF to PDB conversion. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 15 23:10:21 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 15 Jul 2016 23:10:21 -0000 Subject: [GHC] #12155: Description of flags cut off In-Reply-To: <045.2ffe1ef8d3efab06fe4ba333c1ac3add@haskell.org> References: <045.2ffe1ef8d3efab06fe4ba333c1ac3add@haskell.org> Message-ID: <060.a5b30516f54a88b1a3862cc6a323fd52@haskell.org> #12155: Description of flags cut off -------------------------------------+------------------------------------- Reporter: mikail | Owner: Type: task | Status: new Priority: low | Milestone: Component: Documentation | Version: 8.0.1 Resolution: | Keywords: flags 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 mikail): Would it be possible to switch to Pandoc. It's multi line table option would do the trick. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jul 16 08:25:06 2016 From: ghc-devs at haskell.org (GHC) Date: Sat, 16 Jul 2016 08:25:06 -0000 Subject: [GHC] #12397: Support for PDB debug information generation In-Reply-To: <045.7bf08882b414350a48568f9ca1e85e23@haskell.org> References: <045.7bf08882b414350a48568f9ca1e85e23@haskell.org> Message-ID: <060.d563606a01b0b3ce925f59e83fd6d2bb@haskell.org> #12397: Support for PDB debug information generation -------------------------------------+------------------------------------- Reporter: varosi | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 (Debugging) | 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 Phyx-): One easier way would be to re-use the `llvm` PDB code[1]. It's nicely separated out and should be easy to plug in. Code seems to be on an MIT license. [1]https://github.com/llvm-mirror/llvm/tree/master/lib/DebugInfo/PDB -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jul 16 13:55:35 2016 From: ghc-devs at haskell.org (GHC) Date: Sat, 16 Jul 2016 13:55:35 -0000 Subject: [GHC] #12399: DeriveFunctor fail Message-ID: <043.b1fcb56ccca9ba47ddb9663057b5be5a@haskell.org> #12399: DeriveFunctor fail -------------------------------------+------------------------------------- Reporter: osa1 | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.1 (Type checker) | 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: -------------------------------------+------------------------------------- {{{#!haskell {-# LANGUAGE DeriveFunctor, MagicHash, UnboxedTuples #-} module Lib where import GHC.Exts newtype RmLoopsM a = RmLoopsM { runRmLoops :: Int# -> (# Int#, a #) } }}} Functor instance for this can be derived like this: {{{#!haskell instance Functor RmLoopsM where fmap f (RmLoopsM m) = RmLoopsM $ \i -> case m i of (# i', r #) -> (# i', f r #) }}} `DeriveFunctor` instead generates something like this: {{{#!haskell instance Functor RmLoopsM where fmap f_a2Oh (Lib.RmLoopsM a1_a2Oi) = RmLoopsM ((\ b6_a2Oj b7_a2Ok -> (\ b5_a2Ol -> case b5_a2Ol of { ((#,#) a1_a2Om a2_a2On a3_a2Oo a4_a2Op) -> (#,#) ((\ b2_a2Oq -> b2_a2Oq) a1_a2Om) ((\ b3_a2Or -> b3_a2Or) a2_a2On) ((\ b4_a2Os -> b4_a2Os) a3_a2Oo) (f_a2Oh a4_a2Op) }) (b6_a2Oj ((\ b1_a2Ot -> b1_a2Ot) b7_a2Ok))) a1_a2Oi) }}} which fails with {{{ Main.hs:17:25: error: • The constructor ‘(#,#)’ should have 2 arguments, but has been given 4 • In the pattern: (#,#) a1_a2Om a2_a2On a3_a2Oo a4_a2Op In a case alternative: ((#,#) a1_a2Om a2_a2On a3_a2Oo a4_a2Op) -> (#,#) ((\ b2_a2Oq -> b2_a2Oq) a1_a2Om) ((\ b3_a2Or -> b3_a2Or) a2_a2On) ((\ b4_a2Os -> b4_a2Os) a3_a2Oo) (f_a2Oh a4_a2Op) In the expression: case b5_a2Ol of { ((#,#) a1_a2Om a2_a2On a3_a2Oo a4_a2Op) -> (#,#) ((\ b2_a2Oq -> b2_a2Oq) a1_a2Om) ((\ b3_a2Or -> b3_a2Or) a2_a2On) ((\ b4_a2Os -> b4_a2Os) a3_a2Oo) (f_a2Oh a4_a2Op) } }}} I think it's supposed to ignore RuntimeRep args during the fold (`TcGenDeriv.functorLikeTraverse`). Tried with: HEAD, 8.0.1. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jul 16 14:27:11 2016 From: ghc-devs at haskell.org (GHC) Date: Sat, 16 Jul 2016 14:27:11 -0000 Subject: [GHC] #12400: Suggest misspelling if a type signature has similarly named binding Message-ID: <051.03646b2db837f69c01b37ea92467b9da@haskell.org> #12400: Suggest misspelling if a type signature has similarly named binding -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: feature | Status: new request | Priority: lowest | Milestone: Component: Compiler | Version: 8.0.1 Keywords: | 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: -------------------------------------+------------------------------------- Due to clumsy fingers I often run into {{{#!hs mkBinder :: a mkBidner = undefined }}} errors with {{{ t1ZE.hs:1:1-8: error: … The type signature for ‘mkBinder’ lacks an accompanying binding Compilation failed. }}} Maybe it could mention {{{ note: did you mean 'mkBinder'? }}} ---- How `clang` does it {{{#!c #include int main(void) { prinft("hi"); } }}} {{{ % clang -Werror c.c c.c:5:3: error: implicit declaration of function 'prinft' is invalid in C99 [-Werror,-Wimplicit-function-declaration] prinft("hi"); ^ c.c:5:3: note: did you mean 'printf'? /usr/include/stdio.h:362:12: note: 'printf' declared here extern int printf (const char *__restrict __format, ...); ^ 1 error generated. baldur at Loki:/tmp$ }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jul 16 14:27:50 2016 From: ghc-devs at haskell.org (GHC) Date: Sat, 16 Jul 2016 14:27:50 -0000 Subject: [GHC] #12400: Suggest misspelling if a type signature has similarly named binding In-Reply-To: <051.03646b2db837f69c01b37ea92467b9da@haskell.org> References: <051.03646b2db837f69c01b37ea92467b9da@haskell.org> Message-ID: <066.4201c65f4aa2a6bc60396df11b33b3d5@haskell.org> #12400: Suggest misspelling if a type signature has similarly named binding -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: feature request | Status: new Priority: lowest | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: 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: | -------------------------------------+------------------------------------- Description changed by Iceland_jack: @@ -46,1 +46,0 @@ - baldur at Loki:/tmp$ New description: Due to clumsy fingers I often run into {{{#!hs mkBinder :: a mkBidner = undefined }}} errors with {{{ t1ZE.hs:1:1-8: error: … The type signature for ‘mkBinder’ lacks an accompanying binding Compilation failed. }}} Maybe it could mention {{{ note: did you mean 'mkBinder'? }}} ---- How `clang` does it {{{#!c #include int main(void) { prinft("hi"); } }}} {{{ % clang -Werror c.c c.c:5:3: error: implicit declaration of function 'prinft' is invalid in C99 [-Werror,-Wimplicit-function-declaration] prinft("hi"); ^ c.c:5:3: note: did you mean 'printf'? /usr/include/stdio.h:362:12: note: 'printf' declared here extern int printf (const char *__restrict __format, ...); ^ 1 error generated. }}} -- -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jul 16 17:23:58 2016 From: ghc-devs at haskell.org (GHC) Date: Sat, 16 Jul 2016 17:23:58 -0000 Subject: [GHC] #12401: GHC panic! Template variable unbound in rewrite rule Message-ID: <048.bb29ad43ef422a099b000889adb7e842@haskell.org> #12401: GHC panic! Template variable unbound in rewrite rule -------------------------------------+------------------------------------- Reporter: vagarenko | Owner: Type: bug | Status: new Priority: high | Milestone: Component: Compiler | Version: 8.0.1 Keywords: | Operating System: Windows Architecture: x86_64 | Type of failure: Compile-time (amd64) | crash Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- When compiling following code with `-O`: {{{#!hs {-# LANGUAGE FlexibleContexts, TypeFamilies, TypeSynonymInstances #-} module Bug where import Data.Word import Foreign.Storable import qualified Data.Vector.Storable as VS data Image a = Image { imageWidth :: !Int , imageHeight :: !Int , imageData :: VS.Vector (PixelBaseComponent a) } class (Storable (PixelBaseComponent a)) => Pixel a where type PixelBaseComponent a :: * instance Pixel Pixel8 where type PixelBaseComponent Pixel8 = Word8 instance Pixel Pixel16 where type PixelBaseComponent Pixel16 = Word16 data DynamicImage = ImageY8 (Image Pixel8) | ImageY16 (Image Pixel16) type Pixel8 = Word8 type Pixel16 = Word16 -- | imageMirrorY :: DynamicImage -> DynamicImage imageMirrorY dynImg = case dynImg of ImageY8 img -> ImageY8 $ mirror img 1 ImageY16 img -> ImageY16 $ mirror img 1 where mirror img channels = img { imageData = VS.concat $ reverse $ map (\y -> VS.slice (y * rowLen) rowLen (imageData img)) [0 .. imageHeight img - 1] } where rowLen = channels * imageWidth img }}} I get error: {{{ > ghc Bug -O [1 of 1] Compiling Bug ( Bug.hs, Bug.o ) ghc: panic! (the 'impossible' happened) (GHC version 8.0.1 for x86_64-unknown-mingw32): Template variable unbound in rewrite rule Variable: cobox_s5Rv Rule "SPEC mirror @ Pixel8 @ Pixel8" Rule bndrs: [cobox_s5Rv, $dStorable_s5Rw] LHS args: [TYPE: Pixel8, TYPE: Pixel8, CO: _N, $dStorable_s5Rw] Actual args: [TYPE: Pixel8, TYPE: Pixel8, CO: _N, $fStorableWord8 `cast` ((Storable (Sym D:R:PixelBaseComponentWord8[0]))_R :: (Storable Word8 :: Constraint) ~R# (Storable (PixelBaseComponent Pixel8) :: Constraint)), img_a4IS, lvl_s7o4] 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 Sat Jul 16 17:47:13 2016 From: ghc-devs at haskell.org (GHC) Date: Sat, 16 Jul 2016 17:47:13 -0000 Subject: [GHC] #12401: GHC panic! Template variable unbound in rewrite rule In-Reply-To: <048.bb29ad43ef422a099b000889adb7e842@haskell.org> References: <048.bb29ad43ef422a099b000889adb7e842@haskell.org> Message-ID: <063.cccb14896cc33c6708be6b432d7f0a81@haskell.org> #12401: GHC panic! Template variable unbound in rewrite rule -------------------------------------+------------------------------------- Reporter: vagarenko | Owner: Type: bug | Status: new Priority: high | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Windows | Architecture: x86_64 Type of failure: Compile-time | (amd64) crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by vagarenko): If I provide type signature for `mirror`: {{{#!hs mirror :: (Storable (PixelBaseComponent a)) => Image a -> Int -> Image a }}} it compiles fine. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jul 16 18:47:03 2016 From: ghc-devs at haskell.org (GHC) Date: Sat, 16 Jul 2016 18:47:03 -0000 Subject: [GHC] #12399: DeriveFunctor fail In-Reply-To: <043.b1fcb56ccca9ba47ddb9663057b5be5a@haskell.org> References: <043.b1fcb56ccca9ba47ddb9663057b5be5a@haskell.org> Message-ID: <058.eb5ff4be7aee956ce8ec17c89d66ed3a@haskell.org> #12399: DeriveFunctor fail -------------------------------------+------------------------------------- Reporter: osa1 | Owner: Type: bug | Status: new Priority: normal | Milestone: 8.2.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): * cc: RyanGlScott (added) * milestone: => 8.2.1 Comment: Adding RyanGlScott who has done a fair bit of work in this area. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jul 16 18:50:40 2016 From: ghc-devs at haskell.org (GHC) Date: Sat, 16 Jul 2016 18:50:40 -0000 Subject: [GHC] #12398: Expose 'withCleanupSession' as a replacement for 'defaultCleanupHandler' In-Reply-To: <046.ae05c9ccdd84834d5d2d4568141d97f7@haskell.org> References: <046.ae05c9ccdd84834d5d2d4568141d97f7@haskell.org> Message-ID: <061.599fef1b3910f803c97808b4bda41044@haskell.org> #12398: Expose 'withCleanupSession' as a replacement for 'defaultCleanupHandler' -------------------------------------+------------------------------------- Reporter: DanielG | Owner: Type: bug | Status: new Priority: normal | Milestone: 8.0.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): * cc: simonmar (added) * milestone: => 8.0.2 Comment: Adding Simon Marlow who deprecated `defaultCleanupHandler` in 4905b83a2d448c65ccced385343d4e8124548a3b. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jul 16 18:53:40 2016 From: ghc-devs at haskell.org (GHC) Date: Sat, 16 Jul 2016 18:53:40 -0000 Subject: [GHC] #12397: Support for PDB debug information generation In-Reply-To: <045.7bf08882b414350a48568f9ca1e85e23@haskell.org> References: <045.7bf08882b414350a48568f9ca1e85e23@haskell.org> Message-ID: <060.078ee36811e9eb68c83deea5a3710c9b@haskell.org> #12397: Support for PDB debug information generation -------------------------------------+------------------------------------- Reporter: varosi | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 (Debugging) | 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 bgamari): Be aware that we are still [[DWARF/80Status|struggling]] to provide correct DWARF annotations. There are still a lot of open questions in this area. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jul 16 18:56:32 2016 From: ghc-devs at haskell.org (GHC) Date: Sat, 16 Jul 2016 18:56:32 -0000 Subject: [GHC] #12388: Don't barf on failures in the RTS linker In-Reply-To: <047.b86bfd9a8524336c9591b8a2b9e093dd@haskell.org> References: <047.b86bfd9a8524336c9591b8a2b9e093dd@haskell.org> Message-ID: <062.36be8321f3212b9e53cf215a82ecee91@haskell.org> #12388: Don't barf on failures in the RTS linker -------------------------------------+------------------------------------- Reporter: dobenour | Owner: Type: bug | Status: new Priority: normal | Milestone: 8.2.1 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: | -------------------------------------+------------------------------------- Changes (by bgamari): * cc: erikd, bgamari, simonmar (added) Comment: Ccing the usual RTS people. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jul 16 19:04:06 2016 From: ghc-devs at haskell.org (GHC) Date: Sat, 16 Jul 2016 19:04:06 -0000 Subject: [GHC] #10352: Properly link Haskell shared libs on all systems (was: Properly link Haskell shared libs on ELF systems) In-Reply-To: <045.f54c0b53e462b1ea305eb5f3c38d7688@haskell.org> References: <045.f54c0b53e462b1ea305eb5f3c38d7688@haskell.org> Message-ID: <060.86a3e7814093e54670d8a414ba097465@haskell.org> #10352: Properly link Haskell shared libs on all systems -------------------------------------+------------------------------------- Reporter: duncan | Owner: Phyx- Type: task | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.11 (Linking) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: 5987 Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by Phyx-): * owner: => Phyx- Comment: Well I'll take a crack at it then since it's currently blocking my progress on dynamic linking on Windows :) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jul 16 19:05:13 2016 From: ghc-devs at haskell.org (GHC) Date: Sat, 16 Jul 2016 19:05:13 -0000 Subject: [GHC] #12401: GHC panic! Template variable unbound in rewrite rule In-Reply-To: <048.bb29ad43ef422a099b000889adb7e842@haskell.org> References: <048.bb29ad43ef422a099b000889adb7e842@haskell.org> Message-ID: <063.a39d14c590fb75a4987da6640e357850@haskell.org> #12401: GHC panic! Template variable unbound in rewrite rule -------------------------------------+------------------------------------- Reporter: vagarenko | Owner: Type: bug | Status: new Priority: high | Milestone: 8.0.2 Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Windows | Architecture: x86_64 Type of failure: Compile-time | (amd64) crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * milestone: => 8.0.2 Comment: Thanks for the rather minimal testcase. It can be minimized a bit further by eliminating the `Pixel{8,16}` synonyms with the RHSs. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jul 16 19:19:02 2016 From: ghc-devs at haskell.org (GHC) Date: Sat, 16 Jul 2016 19:19:02 -0000 Subject: [GHC] #12402: Add fromLeft and fromRight to Data.Either Message-ID: <047.8d07fa3189133dd22d10c5fafc177522@haskell.org> #12402: Add fromLeft and fromRight to Data.Either -------------------------------------+------------------------------------- Reporter: mettekou | Owner: Type: feature | Status: new request | Priority: normal | Milestone: Component: | Version: 8.0.1 libraries/base | Keywords: Data.Either, | Operating System: Unknown/Multiple fromLeft, fromRight | Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- This ticket is the result of [https://mail.haskell.org/pipermail/libraries/2016-June/027093.html the discussion of the proposal on the libraries mailing list] to add the following two functions to Data.Either in base: {{{#!hs fromLeft :: a -> Either a b -> a fromRight :: b -> Either a b -> b }}} The functions extract an {{{Either a b}}} value for the constructors in their namesake, providing their first argument as a default value for values created using the other constructor. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jul 16 19:45:11 2016 From: ghc-devs at haskell.org (GHC) Date: Sat, 16 Jul 2016 19:45:11 -0000 Subject: [GHC] #12402: Add fromLeft and fromRight to Data.Either In-Reply-To: <047.8d07fa3189133dd22d10c5fafc177522@haskell.org> References: <047.8d07fa3189133dd22d10c5fafc177522@haskell.org> Message-ID: <062.3bcb2d22d7637fb9ebe21f0b4ea4cb88@haskell.org> #12402: Add fromLeft and fromRight to Data.Either -------------------------------------+------------------------------------- Reporter: mettekou | Owner: Type: feature request | Status: patch Priority: normal | Milestone: Component: libraries/base | Version: 8.0.1 Resolution: | Keywords: Data.Either, | fromLeft, fromRight 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 mettekou): * status: new => patch -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jul 16 19:47:16 2016 From: ghc-devs at haskell.org (GHC) Date: Sat, 16 Jul 2016 19:47:16 -0000 Subject: [GHC] #12402: Add fromLeft and fromRight to Data.Either In-Reply-To: <047.8d07fa3189133dd22d10c5fafc177522@haskell.org> References: <047.8d07fa3189133dd22d10c5fafc177522@haskell.org> Message-ID: <062.92ed8fabf6d8a323ac6b25fb5b15e319@haskell.org> #12402: Add fromLeft and fromRight to Data.Either -------------------------------------+------------------------------------- Reporter: mettekou | Owner: Type: feature request | Status: patch Priority: normal | Milestone: Component: libraries/base | Version: 8.0.1 Resolution: | Keywords: Data.Either, | fromLeft, fromRight Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): D2403 Wiki Page: | -------------------------------------+------------------------------------- Changes (by mettekou): * differential: => D2403 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jul 16 19:58:48 2016 From: ghc-devs at haskell.org (GHC) Date: Sat, 16 Jul 2016 19:58:48 -0000 Subject: [GHC] #12402: Add fromLeft and fromRight to Data.Either In-Reply-To: <047.8d07fa3189133dd22d10c5fafc177522@haskell.org> References: <047.8d07fa3189133dd22d10c5fafc177522@haskell.org> Message-ID: <062.1ac137e34594f735c1d77f00f093991a@haskell.org> #12402: Add fromLeft and fromRight to Data.Either -------------------------------------+------------------------------------- Reporter: mettekou | Owner: Type: feature request | Status: patch Priority: normal | Milestone: Component: libraries/base | Version: 8.0.1 Resolution: | Keywords: Data.Either, | fromLeft, fromRight Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2403 Wiki Page: | -------------------------------------+------------------------------------- Changes (by mpickering): * differential: D2403 => Phab:D2403 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jul 16 21:06:10 2016 From: ghc-devs at haskell.org (GHC) Date: Sat, 16 Jul 2016 21:06:10 -0000 Subject: [GHC] #12399: DeriveFunctor fail In-Reply-To: <043.b1fcb56ccca9ba47ddb9663057b5be5a@haskell.org> References: <043.b1fcb56ccca9ba47ddb9663057b5be5a@haskell.org> Message-ID: <058.2ba86dc0290c7ab330126813ac5d2508@haskell.org> #12399: DeriveFunctor fail -------------------------------------+------------------------------------- Reporter: osa1 | Owner: Type: bug | Status: patch Priority: normal | Milestone: 8.2.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:D2404 Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * status: new => patch * differential: => Phab:D2404 Comment: Nice catch! I had no idea that `RuntimeRep`-kinded type parameters were also represented as actual arguments to a constructor... in any case, your intuition that we need to drop the `RuntimeRep` args was spot on. (Hopefully, this would also fix derived `Functor` instances for datatypes that contain unboxed sums, but I'm not 100% sure on that.) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jul 16 21:40:26 2016 From: ghc-devs at haskell.org (GHC) Date: Sat, 16 Jul 2016 21:40:26 -0000 Subject: [GHC] #11094: Cost-center heap profiler should be able to emit samples to eventlog In-Reply-To: <046.5020b7d3a1ba23f2949a42c6789e9133@haskell.org> References: <046.5020b7d3a1ba23f2949a42c6789e9133@haskell.org> Message-ID: <061.156a5f77a826a99dc85e8495f0b9b5ca@haskell.org> #11094: Cost-center heap profiler should be able to emit samples to eventlog -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: feature request | Status: patch Priority: normal | Milestone: Component: Profiling | Version: 7.10.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Other | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D1722 Wiki Page: | -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"a9bc54766ddd1bdb011f1656ad58fb409055d08f/ghc" a9bc5476/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="a9bc54766ddd1bdb011f1656ad58fb409055d08f" Log heap profiler samples to event log Test Plan: Try it Reviewers: hvr, simonmar, austin, erikd Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D1722 GHC Trac Issues: #11094 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jul 16 22:25:17 2016 From: ghc-devs at haskell.org (GHC) Date: Sat, 16 Jul 2016 22:25:17 -0000 Subject: [GHC] #12388: Don't barf on failures in the RTS linker In-Reply-To: <047.b86bfd9a8524336c9591b8a2b9e093dd@haskell.org> References: <047.b86bfd9a8524336c9591b8a2b9e093dd@haskell.org> Message-ID: <062.1390a76800dcce71926f98f310868f5c@haskell.org> #12388: Don't barf on failures in the RTS linker -------------------------------------+------------------------------------- Reporter: dobenour | Owner: Type: bug | Status: new Priority: normal | Milestone: 8.2.1 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 erikd): I would be the first to agree that the RTS Linker code is nowhere near as nice as it should be be. This code has been put together via accretion over a decade or more. I has had over a dozen people work on it and all of those people know C but would prefer to write Haskell. Another problem is that code has to support at least 6 CPU architecture about 5 different Unix variants and Windows. I personally think porting the linker to C++ is a really bad idea. The linker is already under-resourced (in terms of people working on it) and using C++ instead of C would make it significantly more difficult for newcomers to work on it. As for your other two suggestions I have no strong feelings for or against, but would happy to have anyone work on the linker to help improve it. One last thought, a system using or based on talloc (https://talloc.samba.org/talloc/doc/html/index.html) may help. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jul 16 23:25:37 2016 From: ghc-devs at haskell.org (GHC) Date: Sat, 16 Jul 2016 23:25:37 -0000 Subject: [GHC] #12402: Add fromLeft and fromRight to Data.Either In-Reply-To: <047.8d07fa3189133dd22d10c5fafc177522@haskell.org> References: <047.8d07fa3189133dd22d10c5fafc177522@haskell.org> Message-ID: <062.2e6fb0d3df3bc13ca8abd5e56aad25a2@haskell.org> #12402: Add fromLeft and fromRight to Data.Either -------------------------------------+------------------------------------- Reporter: mettekou | Owner: Type: feature request | Status: closed Priority: normal | Milestone: Component: libraries/base | Version: 8.0.1 Resolution: fixed | Keywords: Data.Either, | fromLeft, fromRight Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2403 Wiki Page: | -------------------------------------+------------------------------------- Changes (by mettekou): * status: patch => closed * resolution: => fixed -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jul 16 23:28:29 2016 From: ghc-devs at haskell.org (GHC) Date: Sat, 16 Jul 2016 23:28:29 -0000 Subject: [GHC] #12403: Template Haskell boxes tuple types when reifying them Message-ID: <050.3278a8386bb0a4b6b9320911f2b0a639@haskell.org> #12403: Template Haskell boxes tuple types when reifying them -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: bug | Status: new Priority: normal | Milestone: 8.0.2 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: -------------------------------------+------------------------------------- Example: {{{#!hs {-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE UnboxedTuples #-} module Main where import Language.Haskell.TH data T = T (# Int, Int #) $(return []) main :: IO () main = putStrLn $(reify ''T >>= stringE . pprint) }}} {{{ $ /opt/ghc/8.0.1/bin/ghc -fforce-recomp Constraints.hs [1 of 1] Compiling Main ( Constraints.hs, Constraints.o ) Linking Constraints ... $ ./Constraints data Main.T = Main.T ((,,,) GHC.Types.Int GHC.Types.Int) }}} Patch coming soon. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jul 16 23:28:43 2016 From: ghc-devs at haskell.org (GHC) Date: Sat, 16 Jul 2016 23:28:43 -0000 Subject: [GHC] #12403: Template Haskell boxes unboxed tuple types when reifying them (was: Template Haskell boxes tuple types when reifying them) In-Reply-To: <050.3278a8386bb0a4b6b9320911f2b0a639@haskell.org> References: <050.3278a8386bb0a4b6b9320911f2b0a639@haskell.org> Message-ID: <065.1d7aed6b3c9863996686e23ad22f611c@haskell.org> #12403: Template Haskell boxes unboxed tuple types when reifying them -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: bug | Status: new Priority: normal | Milestone: 8.0.2 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: | -------------------------------------+------------------------------------- -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jul 16 23:47:05 2016 From: ghc-devs at haskell.org (GHC) Date: Sat, 16 Jul 2016 23:47:05 -0000 Subject: [GHC] #12404: Document version availability for each language extension Message-ID: <045.4012266a90a35b27b3ff877b6e2f633e@haskell.org> #12404: Document version availability for each language extension -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: Type: feature | Status: new request | Priority: normal | Milestone: 8.2.1 Component: Documentation | Version: 8.0.1 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: -------------------------------------+------------------------------------- A certain amount of "historical" information about language extensions is of sufficient practical utility to deserve a place in the GHC documentation. I believe that the documentation for each language extension should include 1. The GHC version in which it first appeared. 2. Any major changes that have been made to the extension since the previous major-major version. For example, the GHC 8.x.x documentation for any given language extension should include any major changes to it since 7.0.1. At present, the only way I see to get this information is to dig through previous versions of the documentation and change logs, which is rather inefficient. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jul 16 23:50:45 2016 From: ghc-devs at haskell.org (GHC) Date: Sat, 16 Jul 2016 23:50:45 -0000 Subject: [GHC] #12403: Template Haskell boxes unboxed tuple types when reifying them In-Reply-To: <050.3278a8386bb0a4b6b9320911f2b0a639@haskell.org> References: <050.3278a8386bb0a4b6b9320911f2b0a639@haskell.org> Message-ID: <065.921e21663fb58f281dbb0978021b29eb@haskell.org> #12403: Template Haskell boxes unboxed tuple types when reifying them -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: bug | Status: patch Priority: normal | Milestone: 8.0.2 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): Phab:D2405 Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * status: new => patch * differential: => Phab:D2405 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Jul 17 00:55:29 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 17 Jul 2016 00:55:29 -0000 Subject: [GHC] #8732: Global big object heap allocator lock causes contention In-Reply-To: <044.a362245e1caab544f39c02e92f1f1660@haskell.org> References: <044.a362245e1caab544f39c02e92f1f1660@haskell.org> Message-ID: <059.c8e78d8e8b2c956598f3408b43a354e4@haskell.org> #8732: Global big object heap allocator lock causes contention -------------------------------------+------------------------------------- Reporter: tibbe | Owner: simonmar Type: bug | Status: new Priority: normal | Milestone: Component: Runtime System | Version: 7.6.3 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 dobenour): Ask the TCMalloc or JEmalloc developers? They have solved this problem, and even if GHC can't use them directly, the algorithms used in them could be used. Also, I am wondering if the current large object limit is too small. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Jul 17 01:00:47 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 17 Jul 2016 01:00:47 -0000 Subject: [GHC] #12181: Multi-threaded code on ARM64 GHC runtime doesn't use all available cores In-Reply-To: <045.62ec1d1031a2707c97a15db7c0ee2c82@haskell.org> References: <045.62ec1d1031a2707c97a15db7c0ee2c82@haskell.org> Message-ID: <060.52c844fd9a1249efa8bb51482b293603@haskell.org> #12181: Multi-threaded code on ARM64 GHC runtime doesn't use all available cores --------------------------------------------+------------------------------ Reporter: varosi | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Runtime System | Version: 7.10.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: arm Type of failure: Runtime performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | --------------------------------------------+------------------------------ Comment (by dobenour): What about having a Haskell API to tell the RTS to re-detect the number of CPUs, looking for the number of available processors? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Jul 17 07:53:33 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 17 Jul 2016 07:53:33 -0000 Subject: =?utf-8?q?Re=3A_=5BGHC=5D_=2311632=3A_Data=2EChar_repeated_readL?= =?utf-8?q?itChar_barfs_on_output_from_show_=22=C3=B31=22?= In-Reply-To: <049.9bf2436e7fb9c211d83d1b0ba3c6ee23@haskell.org> References: <049.9bf2436e7fb9c211d83d1b0ba3c6ee23@haskell.org> Message-ID: <064.814352fc6b2f7c9133245df1bcd623e6@haskell.org> #11632: Data.Char repeated readLitChar barfs on output from show "ó1" -------------------------------------+------------------------------------- Reporter: inversemot | Owner: kgupta Type: bug | Status: patch Priority: normal | Milestone: 8.2.1 Component: Core Libraries | Version: 7.10.3 Resolution: | Keywords: newcomer Operating System: Linux | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: readLitChar Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2391 Wiki Page: | -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"0f0cdb6827803015a9a3924fdafaef8dbcde048f/ghc" 0f0cdb68/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="0f0cdb6827803015a9a3924fdafaef8dbcde048f" Bugfix for bug 11632: `readLitChar` should consume null characters Test Plan: The tests have been included. This change deals with a relatively minor edge case and should not break unrelated functionality. Reviewers: thomie, #core_libraries_committee, ekmett, bgamari Reviewed By: #core_libraries_committee, ekmett, bgamari Subscribers: bgamari, ekmett Differential Revision: https://phabricator.haskell.org/D2391 GHC Trac Issues: #11632 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Jul 17 07:53:33 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 17 Jul 2016 07:53:33 -0000 Subject: [GHC] #12227: regression: out of memory with -O2 -ddump-hi on a complex INLINE function In-Reply-To: <046.5eb6cdc259c89a5a386fca350cf30507@haskell.org> References: <046.5eb6cdc259c89a5a386fca350cf30507@haskell.org> Message-ID: <061.3bb50ab7726318c821213915dc5725d5@haskell.org> #12227: regression: out of memory with -O2 -ddump-hi on a complex INLINE function -------------------------------------+------------------------------------- Reporter: j6carey | Owner: Type: bug | Status: patch Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 (CodeGen) | Resolution: | Keywords: Operating System: Linux | Architecture: x86_64 | (amd64) Type of failure: None/Unknown | Test Case: | perf/compiler/T12227 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2397 Wiki Page: | -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"89a8be71a3715c948cebcb19ac81f84da0e6270e/ghc" 89a8be71/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="89a8be71a3715c948cebcb19ac81f84da0e6270e" Pretty: remove a harmful $! (#12227) This is backport of [1] for GHC's copy of Pretty. See Note [Differences between libraries/pretty and compiler/utils/Pretty.hs]. [1] http://git.haskell.org/packages/pretty.git/commit/bbe9270c5f849a5bb74c9166a5f4202cfb0dba22 https://github.com/haskell/pretty/issues/32 https://github.com/haskell/pretty/pull/35 Reviewers: bgamari, austin Reviewed By: austin Differential Revision: https://phabricator.haskell.org/D2397 GHC Trac Issues: #12227 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Jul 17 07:53:33 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 17 Jul 2016 07:53:33 -0000 Subject: [GHC] #9517: hp2ps generates invalid postscript file In-Reply-To: <045.a830b70a270e850cd0392ed106ef100c@haskell.org> References: <045.a830b70a270e850cd0392ed106ef100c@haskell.org> Message-ID: <060.9405c60428f0e42efab08c6522c91e2b@haskell.org> #9517: hp2ps generates invalid postscript file -------------------------------------+------------------------------------- Reporter: JamesM | Owner: Type: bug | Status: patch Priority: normal | Milestone: Component: Profiling | Version: 7.10.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Other | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2398 Wiki Page: | -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"5df92f6776b31b375a80865e7db1f330d929c18f/ghc" 5df92f6/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="5df92f6776b31b375a80865e7db1f330d929c18f" hp2ps: fix invalid PostScript for names with parentheses The names in the .hp files may contain un-matched opening parentheses, so escape them. GHC Trac: #9517 Reviewers: bgamari, austin Reviewed By: bgamari, austin Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2398 GHC Trac Issues: #9517 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Jul 17 07:53:33 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 17 Jul 2016 07:53:33 -0000 Subject: [GHC] #11717: Way to dump cmm only once In-Reply-To: <046.147581339d89f71c221c940bc7bdc90a@haskell.org> References: <046.147581339d89f71c221c940bc7bdc90a@haskell.org> Message-ID: <061.284f3e58695de47be8a0c066c6d3536f@haskell.org> #11717: Way to dump cmm only once -------------------------------------+------------------------------------- Reporter: nomeata | Owner: tvv Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.1 (CodeGen) | 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:D2393 Wiki Page: | -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"1ba79fa4d0e13e61a805fa458bcf2e690710d88b/ghc" 1ba79fa/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="1ba79fa4d0e13e61a805fa458bcf2e690710d88b" CodeGen: Way to dump cmm only once (#11717) The `-ddump-cmm` put all stages of Cmm processing into one output. This patch changes its behavior and adds two more options to make Cmm dumping flexible. - `-ddump-cmm-from-stg` dumps only initial version of Cmm right after STG->Cmm codegen - `-ddump-cmm` dumps the final result of the Cmm pipeline processing - `-ddump-cmm-verbose` dumps intermediate output of each Cmm pipeline step - `-ddump-cmm-proc` and `-ddump-cmm-caf` seems were lost. Now enabled Test Plan: ./validate Reviewers: thomie, simonmar, austin, bgamari Reviewed By: thomie, simonmar Subscribers: simonpj, thomie Differential Revision: https://phabricator.haskell.org/D2393 GHC Trac Issues: #11717 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Jul 17 21:58:28 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 17 Jul 2016 21:58:28 -0000 Subject: [GHC] #12169: libraries/base/dist-install/build/HSbase-4.9.0.0.o: unknown symbol `stat' In-Reply-To: <045.2c9db80d5b79d29cf709346ae32b99ef@haskell.org> References: <045.2c9db80d5b79d29cf709346ae32b99ef@haskell.org> Message-ID: <060.130f23bd28767da247aff26148f4261d@haskell.org> #12169: libraries/base/dist-install/build/HSbase-4.9.0.0.o: unknown symbol `stat' -------------------------------------+------------------------------------- Reporter: thomie | Owner: 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 thomie): According to https://github.com/snowleopard/hadrian/commit/116e64d5596233dcacff48ce7e5e0531f730e6bd, compiling the C files in base with `-O2` (or `-O`?) should fix the problem. I don't understand why. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 18 06:03:02 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 18 Jul 2016 06:03:02 -0000 Subject: [GHC] #12378: Not enough inlining happens with single-method type classes In-Reply-To: <043.6cfc5337b3b4cd84d2c9380280b0d202@haskell.org> References: <043.6cfc5337b3b4cd84d2c9380280b0d202@haskell.org> Message-ID: <058.b9c4d6258288879c76db3cafb18201a3@haskell.org> #12378: Not enough inlining happens with single-method type classes -------------------------------------+------------------------------------- Reporter: akio | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: invalid | 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 akio): * status: new => closed * resolution: => invalid Comment: You are right, it looks like I used the wrong version of the compiler. With GHC 8.0 it works fine. I'm closing the ticket now. I'm sorry for wasting your time. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 18 07:34:44 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 18 Jul 2016 07:34:44 -0000 Subject: [GHC] #12181: Multi-threaded code on ARM64 GHC runtime doesn't use all available cores In-Reply-To: <045.62ec1d1031a2707c97a15db7c0ee2c82@haskell.org> References: <045.62ec1d1031a2707c97a15db7c0ee2c82@haskell.org> Message-ID: <060.1692c1d90ac933dffee05637162e2f33@haskell.org> #12181: Multi-threaded code on ARM64 GHC runtime doesn't use all available cores --------------------------------------------+------------------------------ Reporter: varosi | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Runtime System | Version: 7.10.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: arm Type of failure: Runtime performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | --------------------------------------------+------------------------------ Comment (by simonmar): You can already do this, with `GHC.Conc.getNumberOfProcessors` followed by `GHC.Conc.setNumCapabilities`. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 18 07:42:34 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 18 Jul 2016 07:42:34 -0000 Subject: [GHC] #11427: superclasses aren't considered because context is no smaller than the instance head In-Reply-To: <045.5bbd322743d829f91b935ee5364b27b3@haskell.org> References: <045.5bbd322743d829f91b935ee5364b27b3@haskell.org> Message-ID: <060.de9c715cb5179e93e7c1b98a4e2efc21@haskell.org> #11427: superclasses aren't considered because context is no smaller than the instance head -------------------------------------+------------------------------------- Reporter: phadej | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1-rc1 Resolution: | Keywords: 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 simonpj): It doesn't "reduce the normal language". It does reduce the scope of a tricky and ill-documented extension of Haskell, implemented by GHC, namely the ability to solve recursive instances. And it's tied up with an implementation trick called "silent superclasses" which I used to help, but which ultimately turned out to have several horrid and unforseen consequences. In short, I do not know now to do better. But maybe someone else will! -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 18 07:44:09 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 18 Jul 2016 07:44:09 -0000 Subject: [GHC] #12388: Don't barf on failures in the RTS linker In-Reply-To: <047.b86bfd9a8524336c9591b8a2b9e093dd@haskell.org> References: <047.b86bfd9a8524336c9591b8a2b9e093dd@haskell.org> Message-ID: <062.f5221b602b49f789f32243326d965b02@haskell.org> #12388: Don't barf on failures in the RTS linker -------------------------------------+------------------------------------- Reporter: dobenour | Owner: Type: bug | Status: new Priority: normal | Milestone: 8.2.1 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 simonmar): I already fixed a bunch of these in 5300099edf106c1f5938c0793bd6ca199a0eebf0, but there are definitely more. I think you're talking about `loadArchive`, right? That's where I ran out of energy, because it needs a lot of refactoring. C++ would make it easy, but I don't think it's worth going to C++ just for this one bit of code. I would refactor it carefully, splitting up the function into smaller pieces and building a decent test suite. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 18 07:50:35 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 18 Jul 2016 07:50:35 -0000 Subject: [GHC] #12398: Expose 'withCleanupSession' as a replacement for 'defaultCleanupHandler' In-Reply-To: <046.ae05c9ccdd84834d5d2d4568141d97f7@haskell.org> References: <046.ae05c9ccdd84834d5d2d4568141d97f7@haskell.org> Message-ID: <061.ef0b6727a62f460d2f568111b076099b@haskell.org> #12398: Expose 'withCleanupSession' as a replacement for 'defaultCleanupHandler' -------------------------------------+------------------------------------- Reporter: DanielG | Owner: Type: bug | Status: new Priority: normal | Milestone: 8.0.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: | -------------------------------------+------------------------------------- Comment (by simonmar): Ok, I can see why you might not want the signal handlers installed. But you probably want the other stuff that `runGhc` does, like initialising the DynFlags and the HscEnv, right? Or do you want to use your own `runGhc`? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 18 08:01:51 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 18 Jul 2016 08:01:51 -0000 Subject: [GHC] #12388: Don't barf on failures in the RTS linker In-Reply-To: <047.b86bfd9a8524336c9591b8a2b9e093dd@haskell.org> References: <047.b86bfd9a8524336c9591b8a2b9e093dd@haskell.org> Message-ID: <062.3f69ac483d1a417f68c5f2da20d79388@haskell.org> #12388: Don't barf on failures in the RTS linker -------------------------------------+------------------------------------- Reporter: dobenour | Owner: Type: bug | Status: new Priority: normal | Milestone: 8.2.1 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 simonmar): Something that might help here is gcc's cleanup attribute: https://gcc.gnu.org/onlinedocs/gcc/Common-Variable-Attributes.html which gives you some of the benefits of RAII in plain C. Going to C++ even for a small bit of the codebase would be a big step because we would have to use g++ as the linker and we get dependencies on C++ standard libs etc. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 18 09:12:47 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 18 Jul 2016 09:12:47 -0000 Subject: [GHC] #12405: Add expansions of abbreviated type names in documentation Message-ID: <042.6d8da388c6808774e666636ec49e3173@haskell.org> #12405: Add expansions of abbreviated type names in documentation -------------------------------------+------------------------------------- Reporter: syd | Owner: Type: task | Status: new Priority: lowest | Milestone: Component: GHC API | 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: -------------------------------------+------------------------------------- Type names are often abbreviated for programmer convenience, but they make using the GHC API much harder for newcomers. I would like to add some documentation to these declarations for ease of use. For example: {{{#!hs type LHsDecl id }}} -> {{{#!hs -- | Located Haskell Declaration type LHsDecl id }}} as opposed to {{{#!hs -- | Left-Hand side Declaration type LHsDecl id }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 18 09:33:58 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 18 Jul 2016 09:33:58 -0000 Subject: [GHC] #12405: Add expansions of abbreviated type names in documentation In-Reply-To: <042.6d8da388c6808774e666636ec49e3173@haskell.org> References: <042.6d8da388c6808774e666636ec49e3173@haskell.org> Message-ID: <057.1d722427695b92bde351f262de4b974a@haskell.org> #12405: Add expansions of abbreviated type names in documentation -------------------------------------+------------------------------------- Reporter: syd | Owner: Type: task | Status: new Priority: lowest | 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): D2406 Wiki Page: | -------------------------------------+------------------------------------- Changes (by syd): * differential: => D2406 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 18 09:34:34 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 18 Jul 2016 09:34:34 -0000 Subject: [GHC] #12405: Add expansions of abbreviated type names in documentation In-Reply-To: <042.6d8da388c6808774e666636ec49e3173@haskell.org> References: <042.6d8da388c6808774e666636ec49e3173@haskell.org> Message-ID: <057.cfd08e1b6f97870cc720d3572a05c72a@haskell.org> #12405: Add expansions of abbreviated type names in documentation -------------------------------------+------------------------------------- Reporter: syd | Owner: Type: task | Status: new Priority: lowest | 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:D2406 Wiki Page: | -------------------------------------+------------------------------------- Changes (by syd): * differential: D2406 => Phab:D2406 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 18 10:08:15 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 18 Jul 2016 10:08:15 -0000 Subject: [GHC] #12382: Rename clashing type variables more consistently In-Reply-To: <046.c5cb956f322074bdfaee0fe12bd9cbb4@haskell.org> References: <046.c5cb956f322074bdfaee0fe12bd9cbb4@haskell.org> Message-ID: <061.a3ef291538382768e133ff9495382530@haskell.org> #12382: Rename clashing type variables more consistently -------------------------------------+------------------------------------- Reporter: nomeata | Owner: nomeata Type: feature request | Status: closed Priority: low | Milestone: 8.2.1 Component: Compiler (Type | Version: 8.1 checker) | 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:D2402 Wiki Page: | -------------------------------------+------------------------------------- Changes (by thomie): * status: patch => closed * resolution: => fixed * milestone: => 8.2.1 Comment: commit cd0750ec96fba9b1683b25954092439c0f267fd7 {{{ Author: Joachim Breitner Date: Tue Jul 12 17:21:07 2016 +0200 tidyOccNames: Rename variables fairly So that > :t (id,id,id) produces (id,id,id) :: (a3 -> a3, a2 -> a2, a1 -> a1) instead of (id,id,id) :: (a2 -> a2, a1 -> a1, a -> a) Differential Revision: https://phabricator.haskell.org/D2402 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 18 10:14:17 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 18 Jul 2016 10:14:17 -0000 Subject: [GHC] #12394: broken (obsolete?) links to user guide In-Reply-To: <049.236b514a0a8df239b8fccae12a734bcb@haskell.org> References: <049.236b514a0a8df239b8fccae12a734bcb@haskell.org> Message-ID: <064.5b9f6df0d223a4060cb0a165b3d7dd13@haskell.org> #12394: broken (obsolete?) links to user guide -------------------------------------+------------------------------------- Reporter: j.waldmann | Owner: 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: | -------------------------------------+------------------------------------- Changes (by thomie): * cc: bgamari (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 18 10:17:42 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 18 Jul 2016 10:17:42 -0000 Subject: [GHC] #12395: Misleading GHCi errors when package is installed In-Reply-To: <047.ba2be8af6e35ce15a9e6f8ef5ab4b38f@haskell.org> References: <047.ba2be8af6e35ce15a9e6f8ef5ab4b38f@haskell.org> Message-ID: <062.cda9c74d7aeb0061bbcb07dc33a0edc9@haskell.org> #12395: Misleading GHCi errors when package is installed -------------------------------------+------------------------------------- Reporter: crockeea | Owner: Type: bug | Status: new Priority: high | Milestone: Component: GHCi | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: #11536 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by thomie): * priority: normal => high * related: => #11536 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 18 10:23:38 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 18 Jul 2016 10:23:38 -0000 Subject: [GHC] #11196: TypeInType performance regressions In-Reply-To: <047.3c2d83be09c012b5e401a7d1fd92ec75@haskell.org> References: <047.3c2d83be09c012b5e401a7d1fd92ec75@haskell.org> Message-ID: <062.3761d6083f79ebbcc3c98557b83ff46d@haskell.org> #11196: TypeInType performance regressions -------------------------------------+------------------------------------- Reporter: goldfire | Owner: Type: bug | Status: new Priority: high | Milestone: 8.0.2 Component: Compiler | Version: 7.11 Resolution: | Keywords: TypeInType 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 bgamari): For the record, `FunTy` was reintroduced by 77bb09270c70455bbd547470c4e995707d19f37d. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 18 10:27:40 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 18 Jul 2016 10:27:40 -0000 Subject: [GHC] #12404: Document version availability for each language extension In-Reply-To: <045.4012266a90a35b27b3ff877b6e2f633e@haskell.org> References: <045.4012266a90a35b27b3ff877b6e2f633e@haskell.org> Message-ID: <060.1f71ae4ad02228a61108013d106a946b@haskell.org> #12404: Document version availability for each language extension -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: Type: feature request | Status: new Priority: normal | Milestone: 8.2.1 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: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by thomie): Fwiw, there is [wiki:LanguagePragmaHistory]. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 18 10:31:14 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 18 Jul 2016 10:31:14 -0000 Subject: [GHC] #12227: regression: out of memory with -O2 -ddump-hi on a complex INLINE function In-Reply-To: <046.5eb6cdc259c89a5a386fca350cf30507@haskell.org> References: <046.5eb6cdc259c89a5a386fca350cf30507@haskell.org> Message-ID: <061.2f114d99e2634045aa8eea95fb649415@haskell.org> #12227: regression: out of memory with -O2 -ddump-hi on a complex INLINE function -------------------------------------+------------------------------------- Reporter: j6carey | Owner: Type: bug | Status: merge Priority: normal | Milestone: 8.2.1 Component: Compiler | Version: 8.0.1 (CodeGen) | Resolution: | Keywords: Operating System: Linux | Architecture: x86_64 | (amd64) Type of failure: Compile-time | Test Case: performance bug | perf/compiler/T12227 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2397 Wiki Page: | -------------------------------------+------------------------------------- Changes (by thomie): * status: patch => merge * failure: None/Unknown => Compile-time performance bug * milestone: => 8.2.1 Comment: To merge this to the 8.0 branch, you'll need 372dbc4e78abfb6b5d72c0fea27a1c858c5cd797 first. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 18 10:46:19 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 18 Jul 2016 10:46:19 -0000 Subject: [GHC] #12406: New not-in-scope behaviour + deferred typed holes = disappearing error messages Message-ID: <044.c9551a60b09d198ee5f397948d731bf8@haskell.org> #12406: New not-in-scope behaviour + deferred typed holes = disappearing error messages -------------------------------------+------------------------------------- Reporter: ertes | Owner: 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 following code snippet (using the [https://hackage.haskell.org/package /ref-tf ref-tf library]) is well-typed, and GHC is fine with it: {{{#!hs import Control.Monad -- comment this out to cause error import Control.Monad.Ref main :: IO () main = newRef (pure ()) >>= join . readRef }}} However, if one comments out the first line, then GHC treats `join` as a typed hole due to #10569, but fails to infer its type, causing errors: {{{ test.hs:10:8-23: error: … • Couldn't match type ‘Ref m0’ with ‘GHC.IORef.IORef’ ... test.hs:10:29-32: error: … Variable not in scope: join :: m0 (f0 ()) -> IO () }}} By default the not-in-scope error is reported, but if `-fdefer-typed- holes` is in effect, only the type error is reported leaving the user (at least me) puzzled. Not-in-scope errors should ''always'' be reported. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 18 11:04:47 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 18 Jul 2016 11:04:47 -0000 Subject: [GHC] #12394: broken (obsolete?) links to user guide In-Reply-To: <049.236b514a0a8df239b8fccae12a734bcb@haskell.org> References: <049.236b514a0a8df239b8fccae12a734bcb@haskell.org> Message-ID: <064.e2cf46cad8abf5084630d867849e4e6f@haskell.org> #12394: broken (obsolete?) links to user guide -------------------------------------+------------------------------------- Reporter: j.waldmann | Owner: 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): There are sadly few satisfying ways to deal with this. All-in-all, neither Sphinx nor DocBook provide terribly satisfying solutions to the problem of stable links into documentation. The few solutions I can think of are all quite terrible, 1. Include a link to the index page of the current documentation in the 404 handler in the `users_guide/` directory 2. Try to manually build a map of redirects from the old URLs to the new pages. I had previously started this but the task ate through its time allowance and I dropped it. Moreover, it wasn't clear that this solution was going to be maintainable going forward given that documentation may continue to change. I'd love to hear suggestions on how to proceed though. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 18 11:07:23 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 18 Jul 2016 11:07:23 -0000 Subject: [GHC] #12406: New not-in-scope behaviour + deferred typed holes = disappearing error messages In-Reply-To: <044.c9551a60b09d198ee5f397948d731bf8@haskell.org> References: <044.c9551a60b09d198ee5f397948d731bf8@haskell.org> Message-ID: <059.956bbc8013853c3ef8b125a7663993e3@haskell.org> #12406: New not-in-scope behaviour + deferred typed holes = disappearing error messages -------------------------------------+------------------------------------- Reporter: ertes | Owner: 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 ertes: @@ -1,2 +1,1 @@ - The following code snippet (using the [https://hackage.haskell.org/package - /ref-tf ref-tf library]) is well-typed, and GHC is fine with it: + The following code snippet is well-typed, and GHC is fine with it: @@ -5,0 +4,2 @@ + {-# LANGUAGE TypeFamilies #-} + @@ -6,1 +7,11 @@ - import Control.Monad.Ref + import Data.IORef + + class MonadRef m where + type Ref m :: * -> * + newRef :: a -> m (Ref m a) + readRef :: Ref m a -> m a + + instance MonadRef IO where + type Ref IO = IORef + newRef = newIORef + readRef = readIORef @@ -12,2 +23,3 @@ - However, if one comments out the first line, then GHC treats `join` as a - typed hole due to #10569, but fails to infer its type, causing errors: + However, if one removes the import of `Control.Monad`, then GHC treats + `join` as a typed hole due to #10569, but fails to infer its type, causing + errors: @@ -16,2 +28,2 @@ - test.hs:10:8-23: error: … - • Couldn't match type ‘Ref m0’ with ‘GHC.IORef.IORef’ + test.hs:17:8-23: error: … + • Couldn't match type ‘Ref m0’ with ‘IORef’ @@ -19,1 +31,1 @@ - test.hs:10:29-32: error: … + test.hs:17:29-32: error: … @@ -24,2 +36,2 @@ - holes` is in effect, only the type error is reported leaving the user (at - least me) puzzled. + holes` is in effect, only the type error is reported and the scope error + just vanishes, leaving the user (at least me) puzzled. New description: The following code snippet is well-typed, and GHC is fine with it: {{{#!hs {-# LANGUAGE TypeFamilies #-} import Control.Monad -- comment this out to cause error import Data.IORef class MonadRef m where type Ref m :: * -> * newRef :: a -> m (Ref m a) readRef :: Ref m a -> m a instance MonadRef IO where type Ref IO = IORef newRef = newIORef readRef = readIORef main :: IO () main = newRef (pure ()) >>= join . readRef }}} However, if one removes the import of `Control.Monad`, then GHC treats `join` as a typed hole due to #10569, but fails to infer its type, causing errors: {{{ test.hs:17:8-23: error: … • Couldn't match type ‘Ref m0’ with ‘IORef’ ... test.hs:17:29-32: error: … Variable not in scope: join :: m0 (f0 ()) -> IO () }}} By default the not-in-scope error is reported, but if `-fdefer-typed- holes` is in effect, only the type error is reported and the scope error just vanishes, leaving the user (at least me) puzzled. Not-in-scope errors should ''always'' be reported. -- -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 18 11:13:13 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 18 Jul 2016 11:13:13 -0000 Subject: [GHC] #11717: Way to dump cmm only once In-Reply-To: <046.147581339d89f71c221c940bc7bdc90a@haskell.org> References: <046.147581339d89f71c221c940bc7bdc90a@haskell.org> Message-ID: <061.db2e7b4070014b0267cbe4d041b7e2b4@haskell.org> #11717: Way to dump cmm only once -------------------------------------+------------------------------------- Reporter: nomeata | Owner: tvv Type: feature request | Status: closed Priority: normal | Milestone: 8.2.1 Component: Compiler | Version: 8.1 (CodeGen) | 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:D2393 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 Mon Jul 18 11:14:11 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 18 Jul 2016 11:14:11 -0000 Subject: [GHC] #12227: regression: out of memory with -O2 -ddump-hi on a complex INLINE function In-Reply-To: <046.5eb6cdc259c89a5a386fca350cf30507@haskell.org> References: <046.5eb6cdc259c89a5a386fca350cf30507@haskell.org> Message-ID: <061.21f30f5f3a6aa868e6d23cd5ee2e0b95@haskell.org> #12227: regression: out of memory with -O2 -ddump-hi on a complex INLINE function -------------------------------------+------------------------------------- Reporter: j6carey | Owner: Type: bug | Status: merge Priority: normal | Milestone: 8.0.2 Component: Compiler | Version: 8.0.1 (CodeGen) | Resolution: | Keywords: Operating System: Linux | Architecture: x86_64 | (amd64) Type of failure: Compile-time | Test Case: performance bug | perf/compiler/T12227 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2397 Wiki Page: | -------------------------------------+------------------------------------- Changes (by thomie): * milestone: 8.2.1 => 8.0.2 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 18 11:14:11 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 18 Jul 2016 11:14:11 -0000 Subject: [GHC] #9517: hp2ps generates invalid postscript file In-Reply-To: <045.a830b70a270e850cd0392ed106ef100c@haskell.org> References: <045.a830b70a270e850cd0392ed106ef100c@haskell.org> Message-ID: <060.9bf3d03c52f3b419fb131460f8e9a6a4@haskell.org> #9517: hp2ps generates invalid postscript file -------------------------------------+------------------------------------- Reporter: JamesM | Owner: Type: bug | Status: merge Priority: normal | Milestone: 8.0.2 Component: Profiling | Version: 7.10.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Other | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2398 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: patch => merge * milestone: => 8.0.2 Comment: Merged. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 18 11:20:17 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 18 Jul 2016 11:20:17 -0000 Subject: [GHC] #12406: New not-in-scope behaviour + deferred typed holes = disappearing error messages In-Reply-To: <044.c9551a60b09d198ee5f397948d731bf8@haskell.org> References: <044.c9551a60b09d198ee5f397948d731bf8@haskell.org> Message-ID: <059.a1e03109591d47d63c9bce6a6f40fe7d@haskell.org> #12406: New not-in-scope behaviour + deferred typed holes = disappearing error messages -------------------------------------+------------------------------------- Reporter: ertes | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: #12170 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by thomie): * failure: None/Unknown => Incorrect warning at compile-time * related: => #12170 Comment: This can serve as a test case for #12170. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 18 11:20:57 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 18 Jul 2016 11:20:57 -0000 Subject: [GHC] #12170: Add flag to control whether out of scope variables should be deferred with -fdefer-typed-holes In-Reply-To: <049.73087dc6a5aa1aa799f9994d0d1022ff@haskell.org> References: <049.73087dc6a5aa1aa799f9994d0d1022ff@haskell.org> Message-ID: <064.3eebe2f95b019f15dcbdc540606c6f38@haskell.org> #12170: Add flag to control whether out of scope variables should be deferred with -fdefer-typed-holes -------------------------------------+------------------------------------- Reporter: mpickering | Owner: 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: #10569, #12156, | Differential Rev(s): #12406 | Wiki Page: | -------------------------------------+------------------------------------- Changes (by thomie): * related: #10569, #12156 => #10569, #12156, #12406 Comment: See #12406 for a test case. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 18 14:11:57 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 18 Jul 2016 14:11:57 -0000 Subject: [GHC] #12399: DeriveFunctor fail In-Reply-To: <043.b1fcb56ccca9ba47ddb9663057b5be5a@haskell.org> References: <043.b1fcb56ccca9ba47ddb9663057b5be5a@haskell.org> Message-ID: <058.d50ba51ef88c525e90321dc10fcd1428@haskell.org> #12399: DeriveFunctor fail -------------------------------------+------------------------------------- Reporter: osa1 | Owner: Type: bug | Status: patch Priority: normal | Milestone: 8.2.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:D2404 Wiki Page: | -------------------------------------+------------------------------------- Comment (by Ryan Scott ): In [changeset:"3fa3fe8a9a8afa67829e12efa5d25b76e58a185a/ghc" 3fa3fe8/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="3fa3fe8a9a8afa67829e12efa5d25b76e58a185a" Make DeriveFunctor work with unboxed tuples Summary: Unboxed tuples have `RuntimeRep` arguments which `-XDeriveFunctor` was mistaking for actual data constructor arguments. As a result, a derived `Functor` instance for a datatype that contained an unboxed tuple would generate twice as many arguments as it needed for an unboxed tuple pattern match or expression. The solution is to simply put `dropRuntimeRepArgs` in the right place. Fixes #12399. Test Plan: ./validate Reviewers: austin, hvr, bgamari Reviewed By: bgamari Subscribers: thomie, osa1 Differential Revision: https://phabricator.haskell.org/D2404 GHC Trac Issues: #12399 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 18 14:11:57 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 18 Jul 2016 14:11:57 -0000 Subject: [GHC] #12403: Template Haskell boxes unboxed tuple types when reifying them In-Reply-To: <050.3278a8386bb0a4b6b9320911f2b0a639@haskell.org> References: <050.3278a8386bb0a4b6b9320911f2b0a639@haskell.org> Message-ID: <065.562916508d5e6b38a65a30bd7c1bac7a@haskell.org> #12403: Template Haskell boxes unboxed tuple types when reifying them -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: bug | Status: patch Priority: normal | Milestone: 8.0.2 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): Phab:D2405 Wiki Page: | -------------------------------------+------------------------------------- Comment (by Ryan Scott ): In [changeset:"514c4a4741f3881672f1ccc1fe6d08a5d596bb87/ghc" 514c4a4/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="514c4a4741f3881672f1ccc1fe6d08a5d596bb87" Fix Template Haskell reification of unboxed tuple types Summary: Previously, Template Haskell reified unboxed tuple types as boxed tuples with twice the appropriate arity. Fixes #12403. Test Plan: make test TEST=T12403 Reviewers: hvr, goldfire, austin, bgamari Reviewed By: goldfire Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2405 GHC Trac Issues: #12403 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 18 14:13:46 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 18 Jul 2016 14:13:46 -0000 Subject: [GHC] #12399: DeriveFunctor fail In-Reply-To: <043.b1fcb56ccca9ba47ddb9663057b5be5a@haskell.org> References: <043.b1fcb56ccca9ba47ddb9663057b5be5a@haskell.org> Message-ID: <058.9cb4a4d49f00045a58be1076bbb5a69b@haskell.org> #12399: DeriveFunctor fail -------------------------------------+------------------------------------- Reporter: osa1 | Owner: Type: bug | Status: closed Priority: normal | Milestone: 8.0.2 Component: Compiler (Type | Version: 8.1 checker) | 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:D2404 Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * status: patch => closed * resolution: => fixed * milestone: 8.2.1 => 8.0.2 Comment: I think this deserves to go into 8.0.2, if possible. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 18 14:14:29 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 18 Jul 2016 14:14:29 -0000 Subject: [GHC] #12399: DeriveFunctor fail In-Reply-To: <043.b1fcb56ccca9ba47ddb9663057b5be5a@haskell.org> References: <043.b1fcb56ccca9ba47ddb9663057b5be5a@haskell.org> Message-ID: <058.6d63fca957ce5b9d6ed726898e9db28f@haskell.org> #12399: DeriveFunctor fail -------------------------------------+------------------------------------- Reporter: osa1 | Owner: Type: bug | Status: merge Priority: normal | Milestone: 8.0.2 Component: Compiler (Type | Version: 8.1 checker) | 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:D2404 Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * status: closed => merge -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 18 14:15:02 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 18 Jul 2016 14:15:02 -0000 Subject: [GHC] #12403: Template Haskell boxes unboxed tuple types when reifying them In-Reply-To: <050.3278a8386bb0a4b6b9320911f2b0a639@haskell.org> References: <050.3278a8386bb0a4b6b9320911f2b0a639@haskell.org> Message-ID: <065.e365820428a2a95c68ebc9dc64724ccb@haskell.org> #12403: Template Haskell boxes unboxed tuple types when reifying them -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: bug | Status: merge Priority: normal | Milestone: 8.0.2 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): Phab:D2405 Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * status: patch => merge -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 18 14:31:18 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 18 Jul 2016 14:31:18 -0000 Subject: [GHC] #12271: Remove magic from type defaulting In-Reply-To: <047.ae1779973d06ce4533efe23eea81797f@haskell.org> References: <047.ae1779973d06ce4533efe23eea81797f@haskell.org> Message-ID: <062.7ea01bbe79397d7c042e681611f21e18@haskell.org> #12271: Remove magic from type defaulting -------------------------------------+------------------------------------- Reporter: crockeea | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: | ExtendedDefaultRules 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 thomie): * keywords: => ExtendedDefaultRules Comment: I think this request is covered by #8171, can you confirm? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 18 15:50:00 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 18 Jul 2016 15:50:00 -0000 Subject: [GHC] #12367: Commit adding instances to GHC.Generics regression compiler performance In-Reply-To: <046.87a5f8a842934b4554eedf79fb6bebbc@haskell.org> References: <046.87a5f8a842934b4554eedf79fb6bebbc@haskell.org> Message-ID: <061.eb8fde8a7ed695806f7e83cbfefc49a5@haskell.org> #12367: Commit adding instances to GHC.Generics regression compiler performance -------------------------------------+------------------------------------- Reporter: bgamari | Owner: bgamari Type: bug | Status: new Priority: normal | Milestone: 8.0.2 Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Generics 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 bgamari): So it appears that something is indeed calling for the `V1` dictionary and is therefore forcing the load of the `GHC.Generics` interface file, {{{ ... end stage interact with inerts } runStage top-level reactions { workitem = [W] $dFoldable_a2pp :: Foldable [] (CDictCan) doTopReact [W] $dFoldable_a2pp :: Foldable [] (CDictCan) matchClassInst pred = Foldable [] Starting fork { Dict fun $fFoldable[] ... } ending fork Dict fun $fFoldable[] Starting fork { Dict fun $fFoldableV1 Starting fork { Declaration for $fFoldableV1 Loading decl for $fFoldableV1 updating EPS_ Need decl for V1 Considering whether to load GHC.Generics {- SYSTEM -} Reading interface for GHC.Generics; reason: Need decl for V1 ... }}} Now to work out what. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 18 15:55:14 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 18 Jul 2016 15:55:14 -0000 Subject: [GHC] #12367: Commit adding instances to GHC.Generics regression compiler performance In-Reply-To: <046.87a5f8a842934b4554eedf79fb6bebbc@haskell.org> References: <046.87a5f8a842934b4554eedf79fb6bebbc@haskell.org> Message-ID: <061.7f6feb766821666d7bc225b2dedce15f@haskell.org> #12367: Commit adding instances to GHC.Generics regression compiler performance -------------------------------------+------------------------------------- Reporter: bgamari | Owner: bgamari Type: bug | Status: new Priority: normal | Milestone: 8.0.2 Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Generics 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 bgamari): This minimal program is enough to trigger `GHC.Generics` to be loaded with 673efccb3b348e9daf23d9e65460691bbea8586e yet not without, {{{#!hs module OhNoTooManyInterfaces where concrep :: Int -> [a] -> [a] concrep x y = concat (take x (repeat y)) }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 18 17:31:32 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 18 Jul 2016 17:31:32 -0000 Subject: [GHC] #12407: Template Haskell thinks an unboxed tuple name is illegal to splice in Message-ID: <050.5a490ad0e0e78330be7bea8026596050@haskell.org> #12407: Template Haskell thinks an unboxed tuple name is illegal to splice in -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: bug | Status: new Priority: normal | Milestone: 8.0.2 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: -------------------------------------+------------------------------------- {{{#!hs {-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE UnboxedTuples #-} module Bug where import Language.Haskell.TH.Lib import Language.Haskell.TH.Syntax $(do let ubxTup = conT (unboxedTupleTypeName 2) `appT` conT ''Int `appT` conT ''Int x <- newName "x" y <- newName "y" [d| f :: $(ubxTup) -> $(ubxTup) f $(conP (unboxedTupleDataName 2) [varP x, varP y]) = $(conE (unboxedTupleDataName 2) `appE` varE x `appE` varE y) |]) }}} {{{ $ /opt/ghc/8.0.1/bin/ghc Bug.hs [1 of 1] Compiling Bug ( Bug.hs, Bug.o ) Bug.hs:8:3: error: Illegal type constructor or class name: ‘(#,#)’ When splicing a TH declaration: f_0 :: GHC.Tuple.(#,#) GHC.Types.Int GHC.Types.Int -> GHC.Tuple.(#,#) GHC.Types.Int GHC.Types.Int }}} Patch coming soon. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 18 17:42:25 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 18 Jul 2016 17:42:25 -0000 Subject: [GHC] #12407: Template Haskell thinks an unboxed tuple name is illegal to splice in In-Reply-To: <050.5a490ad0e0e78330be7bea8026596050@haskell.org> References: <050.5a490ad0e0e78330be7bea8026596050@haskell.org> Message-ID: <065.ca7ae9eb243510ebab2a9f147df4a19c@haskell.org> #12407: Template Haskell thinks an unboxed tuple name is illegal to splice in -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: bug | Status: patch Priority: normal | Milestone: 8.0.2 Component: Template Haskell | Version: 8.0.1 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:D2410 Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * status: new => patch * differential: => Phab:D2410 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 18 17:52:35 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 18 Jul 2016 17:52:35 -0000 Subject: [GHC] #12407: Template Haskell thinks an unboxed tuple name is illegal to splice in In-Reply-To: <050.5a490ad0e0e78330be7bea8026596050@haskell.org> References: <050.5a490ad0e0e78330be7bea8026596050@haskell.org> Message-ID: <065.36bed32cba329f05517a0b5cc8ee0b24@haskell.org> #12407: Template Haskell thinks an unboxed tuple name is illegal to splice in -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: bug | Status: patch Priority: normal | Milestone: 8.0.2 Component: Template Haskell | Version: 8.0.1 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:D2410 Wiki Page: | -------------------------------------+------------------------------------- Comment (by Ryan Scott ): In [changeset:"1fc41d3274b5bf62f027aa6c7df57998db494938/ghc" 1fc41d32/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="1fc41d3274b5bf62f027aa6c7df57998db494938" Make okConIdOcc recognize unboxed tuples Summary: `okConIdOcc`, which validates that a type or constructor name is valid for splicing using Template Haskell, has a special case for tuples, but neglects to look for unboxed tuples, causing some sensible Template Haskell code involving unboxed tuples to be rejected. Fixes #12407. Test Plan: make test TEST=T12407 Reviewers: austin, bgamari, hvr, goldfire Reviewed By: goldfire Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2410 GHC Trac Issues: #12407 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 18 17:53:19 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 18 Jul 2016 17:53:19 -0000 Subject: [GHC] #12407: Template Haskell thinks an unboxed tuple name is illegal to splice in In-Reply-To: <050.5a490ad0e0e78330be7bea8026596050@haskell.org> References: <050.5a490ad0e0e78330be7bea8026596050@haskell.org> Message-ID: <065.49069f39392daac365591e714f5d0eda@haskell.org> #12407: Template Haskell thinks an unboxed tuple name is illegal to splice in -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: bug | Status: merge Priority: normal | Milestone: 8.0.2 Component: Template Haskell | Version: 8.0.1 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:D2410 Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * status: patch => merge -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 18 18:40:10 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 18 Jul 2016 18:40:10 -0000 Subject: [GHC] #11054: GHC on Windows could not use more than 64 logical processors In-Reply-To: <045.741627474d8a57d1af2339a943171c04@haskell.org> References: <045.741627474d8a57d1af2339a943171c04@haskell.org> Message-ID: <060.96eb43534ec57b592bb6277e924f9b82@haskell.org> #11054: GHC on Windows could not use more than 64 logical processors -------------------------------------+------------------------------------- Reporter: varosi | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Runtime System | Version: 7.10.2 Resolution: | Keywords: Operating System: Windows | Architecture: x86_64 Type of failure: Runtime | (amd64) performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by varosi): It looks like Phab:D2199 is done. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 18 20:31:19 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 18 Jul 2016 20:31:19 -0000 Subject: [GHC] #12398: Expose 'withCleanupSession' as a replacement for 'defaultCleanupHandler' In-Reply-To: <046.ae05c9ccdd84834d5d2d4568141d97f7@haskell.org> References: <046.ae05c9ccdd84834d5d2d4568141d97f7@haskell.org> Message-ID: <061.1ae31d447b9fc7f28d772185ed125a7a@haskell.org> #12398: Expose 'withCleanupSession' as a replacement for 'defaultCleanupHandler' -------------------------------------+------------------------------------- Reporter: DanielG | Owner: Type: bug | Status: new Priority: normal | Milestone: 8.0.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: | -------------------------------------+------------------------------------- Comment (by DanielG): I have my own `GhcT`/`runGhcT` variant that does all the initialization. Ideally a function doing just the important initialization bits would be exported too but it's simple enough that it doesn't bother me either way. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 18 20:35:40 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 18 Jul 2016 20:35:40 -0000 Subject: [GHC] #12404: Document version availability for each language extension In-Reply-To: <045.4012266a90a35b27b3ff877b6e2f633e@haskell.org> References: <045.4012266a90a35b27b3ff877b6e2f633e@haskell.org> Message-ID: <060.0e078558eb370e5410f02f8306b59340@haskell.org> #12404: Document version availability for each language extension -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: Type: feature request | Status: new Priority: normal | Milestone: 8.2.1 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: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by dfeuer): Replying to [comment:1 thomie]: > Fwiw, there is [wiki:LanguagePragmaHistory]. Imitation is the sincerest form of flattery. I think this is something that belongs in the GHC documentation proper. And that list does not (yet) include many details on changes made to the extensions from version to version. There have been some wobbles around `PolyKinds`, for example, although I don't know the details, and several changes to `PatternSynonyms` from 7.8 to 8.0. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 18 21:51:10 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 18 Jul 2016 21:51:10 -0000 Subject: [GHC] #12407: Template Haskell thinks an unboxed tuple name is illegal to splice in In-Reply-To: <050.5a490ad0e0e78330be7bea8026596050@haskell.org> References: <050.5a490ad0e0e78330be7bea8026596050@haskell.org> Message-ID: <065.35c0c1614815c49cbc10b480d00f4c4f@haskell.org> #12407: Template Haskell thinks an unboxed tuple name is illegal to splice in -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: bug | Status: merge Priority: normal | Milestone: 8.0.2 Component: Template Haskell | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: th/T12407 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2410 Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * testcase: => th/T12407 Comment: Thanks Ryan. Don't forget to fill in the test casel field on the ticket. (I have done so.) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 18 21:57:22 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 18 Jul 2016 21:57:22 -0000 Subject: [GHC] #12399: DeriveFunctor fail In-Reply-To: <043.b1fcb56ccca9ba47ddb9663057b5be5a@haskell.org> References: <043.b1fcb56ccca9ba47ddb9663057b5be5a@haskell.org> Message-ID: <058.9af0fc8d07628dd2dd955fcd7dc508b3@haskell.org> #12399: DeriveFunctor fail -------------------------------------+------------------------------------- Reporter: osa1 | Owner: Type: bug | Status: merge Priority: normal | Milestone: 8.0.2 Component: Compiler (Type | Version: 8.1 checker) | Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | deriving/should_compile/T12399 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2404 Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * testcase: => deriving/should_compile/T12399 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 18 21:58:33 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 18 Jul 2016 21:58:33 -0000 Subject: [GHC] #12403: Template Haskell boxes unboxed tuple types when reifying them In-Reply-To: <050.3278a8386bb0a4b6b9320911f2b0a639@haskell.org> References: <050.3278a8386bb0a4b6b9320911f2b0a639@haskell.org> Message-ID: <065.f312737ec663ad8f2f3bd05b794d27d1@haskell.org> #12403: Template Haskell boxes unboxed tuple types when reifying them -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: bug | Status: merge Priority: normal | Milestone: 8.0.2 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: th/T12403 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2405 Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * testcase: => th/T12403 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 18 23:19:24 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 18 Jul 2016 23:19:24 -0000 Subject: [GHC] #12367: Commit adding instances to GHC.Generics regression compiler performance In-Reply-To: <046.87a5f8a842934b4554eedf79fb6bebbc@haskell.org> References: <046.87a5f8a842934b4554eedf79fb6bebbc@haskell.org> Message-ID: <061.c39c1ba9bdfae283107ab3d4a3aeab84@haskell.org> #12367: Commit adding instances to GHC.Generics regression compiler performance -------------------------------------+------------------------------------- Reporter: bgamari | Owner: bgamari Type: bug | Status: new Priority: normal | Milestone: 8.0.2 Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Generics 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 bgamari): I've made a bit of progress tracking down the cause of GHC.Generics being loaded when looking for a `Foldable []` instance. It looks like the cause is the evaluation of the `mod` binding in IfaceEnv.instIsVisible. The RHS of this binding pulls on is_dfun to get its `idName` (which it only need the Module from). -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 18 23:35:27 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 18 Jul 2016 23:35:27 -0000 Subject: [GHC] #12367: Commit adding instances to GHC.Generics regression compiler performance In-Reply-To: <046.87a5f8a842934b4554eedf79fb6bebbc@haskell.org> References: <046.87a5f8a842934b4554eedf79fb6bebbc@haskell.org> Message-ID: <061.1086eb98bbf66b2f9426287a0565d156@haskell.org> #12367: Commit adding instances to GHC.Generics regression compiler performance -------------------------------------+------------------------------------- Reporter: bgamari | Owner: bgamari Type: bug | Status: new Priority: normal | Milestone: 8.0.2 Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Generics 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 simonpj): * cc: ezyang (added) Comment: Great catch! This is all Edward's fault :-). {{{ commit 4c834fdddf4d44d12039da4d6a2c63a660975b95 Author: Edward Z. Yang Date: Mon Nov 17 21:23:52 2014 -0800 }}} The `is_dfun` field of a `ClsInst` should be lazy, only pulled on if the instance is actually needed. See the `forkM` in `TcIface.tcIfaceInst`. But this `instIsVisible` stuff is pulling on the `is_dfun` which forces lots of stuff to get loaded that is entirely unnecessary. Solution: add an `is_mod :: Module` field to `ClsInst`, which gives the `Module` for the `ClsInst`. Invariant: it's the same Module as that for the `is_dfun`. And use that `is_mod` field in `instIsVisible`. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 18 23:39:02 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 18 Jul 2016 23:39:02 -0000 Subject: [GHC] #12400: Suggest misspelling if a type signature has similarly named binding In-Reply-To: <051.03646b2db837f69c01b37ea92467b9da@haskell.org> References: <051.03646b2db837f69c01b37ea92467b9da@haskell.org> Message-ID: <066.d528646651bbabca4c7bbc84e2c79a98@haskell.org> #12400: Suggest misspelling if a type signature has similarly named binding -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: feature request | Status: new Priority: lowest | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: 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 simonpj): Great idea! I often make this mistake myself. Any volunteers? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 19 05:55:08 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 19 Jul 2016 05:55:08 -0000 Subject: [GHC] #12367: Commit adding instances to GHC.Generics regression compiler performance In-Reply-To: <046.87a5f8a842934b4554eedf79fb6bebbc@haskell.org> References: <046.87a5f8a842934b4554eedf79fb6bebbc@haskell.org> Message-ID: <061.dd1485fbc75f22ce3e670e425c5c8caf@haskell.org> #12367: Commit adding instances to GHC.Generics regression compiler performance -------------------------------------+------------------------------------- Reporter: bgamari | Owner: bgamari Type: bug | Status: patch Priority: normal | Milestone: 8.0.2 Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Generics 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:D2411 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => patch * differential: => Phab:D2411 Comment: Here's a quick attempt at fixing this. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 19 06:09:24 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 19 Jul 2016 06:09:24 -0000 Subject: [GHC] #12367: Commit adding instances to GHC.Generics regression compiler performance In-Reply-To: <046.87a5f8a842934b4554eedf79fb6bebbc@haskell.org> References: <046.87a5f8a842934b4554eedf79fb6bebbc@haskell.org> Message-ID: <061.0517fe89c6370d98ae0ba7eb9da15592@haskell.org> #12367: Commit adding instances to GHC.Generics regression compiler performance -------------------------------------+------------------------------------- Reporter: bgamari | Owner: bgamari Type: bug | Status: patch Priority: normal | Milestone: 8.0.2 Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Generics 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:D2411 Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): One thing I also noticed while debugging this is that the `relevantBindings` logic in `TcErrors` appears to pull in `GHC.Generics` when generating an error, even when no relevant bindings are shown in the resulting message (and even with `-fmax-relevant-binds=0`). Judging from the comments surrounding `relevantBindings`, it sounds like this is expected behavior but I thought I'd mention it anyways. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 19 06:39:40 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 19 Jul 2016 06:39:40 -0000 Subject: [GHC] #12408: "ghc: panic! (the 'impossible' happened)" only when compiled with "-O" Message-ID: <046.d29ea653b6a5476c1904e0cd28bb26ab@haskell.org> #12408: "ghc: panic! (the 'impossible' happened)" only when compiled with "-O" -------------------------------------+------------------------------------- Reporter: clinton | Owner: 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 Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- On Debian GNU/Linux x86, GHC 8.0.1 crashes compiling the attached code, but only when "-O1" is given. Without optimization, it compiles fine. {{{#!hs {-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE FlexibleContexts #-} module Main where import Prelude hiding ( (.) , (+) , (*) ) import qualified Prelude main :: IO () main = return () x :: Int x = 42 f a b c = (c * (a + b)) == ((c * a) + (c * b)) g = f x x x newtype Sum a = Sum { getSum :: a } newtype Product a = Product { getProduct :: a } type family CatParam t :: * class Semigroupoid p where type CatSrc p t :: * type CatDest p t :: * type CatT p a b :: * (.) :: ( p ~ CatParam catAB, p ~ CatParam catBC, p ~ CatParam catAC, a ~ CatSrc p catAB, b ~ CatSrc p catBC, a ~ CatSrc p catAC, b ~ CatDest p catAB, c ~ CatDest p catBC, c ~ CatDest p catAC, catAB ~ CatT p a b, catBC ~ CatT p b c, catAC ~ CatT p a c ) => catBC -> catAB -> catAC data BasicSumSemigroup (t :: *) :: * type instance CatParam (Sum Int) = BasicSumSemigroup Int instance (Num t) => Semigroupoid (BasicSumSemigroup t) where type CatSrc (BasicSumSemigroup _) _ = () type CatDest (BasicSumSemigroup _) _ = () type CatT (BasicSumSemigroup t) _ _ = Sum t (Sum x) . (Sum y) = Sum ((Prelude.+) x y) data BasicProductSemigroup (t :: *) :: * type instance CatParam (Product Int) = BasicProductSemigroup Int instance (Num t) => Semigroupoid (BasicProductSemigroup t) where type CatSrc (BasicProductSemigroup _) _ = () type CatDest (BasicProductSemigroup _) _ = () type CatT (BasicProductSemigroup t) _ _ = Product t (Product x) . (Product y) = Product ((Prelude.*) x y) type family RingParamFromSum p :: * type family RingParamFromProduct p :: * class NearRingWithoutId t where type SumP t type ProdP t type LeftDistrib t origLeftCat rightArg type RightDistrib t origLeftCat leftArg (+) :: ( t ~ RingParamFromSum sumP, Semigroupoid sumP, p ~ sumP, p ~ CatParam catAB, p ~ CatParam catBC, p ~ CatParam catAC, a ~ CatSrc p catAB, b ~ CatSrc p catBC, a ~ CatSrc p catAC, b ~ CatDest p catAB, c ~ CatDest p catBC, c ~ CatDest p catAC, catAB ~ CatT p a b, catBC ~ CatT p b c, catAC ~ CatT p a c, catAB ~ Sum noSumCatAB, catBC ~ Sum noSumCatBC, catAC ~ Sum noSumCatAC ) => noSumCatBC -> noSumCatAB -> noSumCatAC (+) x y = getSum ((Sum x) . (Sum y)) (*) :: ( t ~ RingParamFromProduct prodP, Semigroupoid prodP, p ~ prodP, p ~ CatParam catAB, p ~ CatParam catBC, p ~ CatParam catAC, a ~ CatSrc p catAB, b ~ CatSrc p catBC, a ~ CatSrc p catAC, b ~ CatDest p catAB, c ~ CatDest p catBC, c ~ CatDest p catAC, catAB ~ CatT p a b, catBC ~ CatT p b c, catAC ~ CatT p a c, catAB ~ Product noProdCatAB, catBC ~ Product noProdCatBC, catAC ~ Product noProdCatAC, sumCatAB ~ Sum noProdCatAB, sumCatBC ~ Sum noProdCatBC, sumCatAC ~ Sum noProdCatAC, ps ~ sumP, ps ~ CatParam sumCatAB, ps ~ CatParam sumCatBC, ps ~ CatParam sumCatAC, sumABSrc ~ CatSrc p sumCatAB, sumBCSrc ~ CatSrc p sumCatBC, sumACSrc ~ CatSrc p sumCatAC, sumABDest ~ CatDest p sumCatAB, sumBCDest ~ CatDest p sumCatBC, sumACDest ~ CatDest p sumCatAC, sumACSrc ~ LeftDistrib t sumBCSrc noProdCatAB, sumACSrc ~ RightDistrib t sumACSrc noProdCatBC, sumACDest ~ LeftDistrib t sumBCDest noProdCatAB, sumACDest ~ RightDistrib t sumACDest noProdCatBC ) => noProdCatBC -> noProdCatAB -> noProdCatAC (*) x y = getProduct ((Product x) . (Product y)) data TestInt type instance RingParamFromSum (BasicSumSemigroup Int) = TestInt type instance RingParamFromProduct (BasicProductSemigroup Int) = TestInt instance NearRingWithoutId TestInt where type SumP TestInt = BasicSumSemigroup Int type ProdP TestInt = BasicProductSemigroup Int type LeftDistrib TestInt _ _ = () type RightDistrib TestInt _ _ = () }}} The following error results: {{{ ghc: panic! (the 'impossible' happened) (GHC version 8.0.1 for x86_64-unknown-linux): Template variable unbound in rewrite rule Variable: cobox_s3PM Rule "SPEC f @ Int @ Int @ Int @ Int @ Int @ Int @ Int" Rule bndrs: [cobox_s3PM, cobox_s3PN, cobox_s3PO, cobox_s3PP, cobox_s3PQ, cobox_s3PR, cobox_s3PS, cobox_s3PT, cobox_s3PU, cobox_s3PV, cobox_s3PW, cobox_s3PX, cobox_s3PY, cobox_s3PZ, cobox_s3Q0, cobox_s3Q1, cobox_s3Q2, cobox_s3Q3, cobox_s3Q4, cobox_s3Q5, cobox_s3Q6, cobox_s3Q7, cobox_s3Q8, cobox_s3Q9, cobox_s3Qa, cobox_s3Qb, cobox_s3Qc, cobox_s3Qd, cobox_s3Qe, cobox_s3Qf, cobox_s3Qg, cobox_s3Qh, cobox_s3Qi, cobox_s3Qj, cobox_s3Qk, cobox_s3Ql, cobox_s3Qm, cobox_s3Qn, cobox_s3Qo, cobox_s3Qp, cobox_s3Qq, cobox_s3Qr, cobox_s3Qs, cobox_s3Qt, cobox_s3Qu, cobox_s3Qv, cobox_s3Qw, cobox_s3Qx, cobox_s3Qy, cobox_s3Qz, cobox_s3QA, cobox_s3QB, $dSemigroupoid_X3SC, $dSemigroupoid_X3SE, $dNearRingWithoutId_s3QE, $dNearRingWithoutId_s3QF, $dEq_s3QG] LHS args: [TYPE: Int, TYPE: Int, TYPE: Int, TYPE: Int, TYPE: Int, TYPE: Int, TYPE: Int, CO: _N, CO: _N, CO: _N, CO: cobox_s3PP, CO: cobox_s3PQ, CO: cobox_s3PR, CO: cobox_s3PS, CO: cobox_s3PT, CO: cobox_s3PU, CO: cobox_s3PV, CO: cobox_s3PW, CO: cobox_s3PX, CO: cobox_s3PY, CO: _N, CO: cobox_s3Q0, CO: _N, CO: cobox_s3Q2, CO: _N, CO: _N, CO: _N, CO: cobox_s3Q6, CO: cobox_s3Q7, CO: cobox_s3Q8, CO: cobox_s3Q9, CO: cobox_s3Qa, CO: cobox_s3Qb, CO: cobox_s3Qc, CO: cobox_s3Qd, CO: cobox_s3Qe, CO: _N, CO: cobox_s3Qg, CO: _N, CO: _N, CO: _N, CO: cobox_s3Qk, CO: cobox_s3Ql, CO: cobox_s3Qm, CO: _N, CO: _N, CO: _N, CO: _N, CO: _N, CO: cobox_s3Qs, CO: _N, CO: cobox_s3Qu, CO: _N, CO: _N, CO: _N, CO: _N, CO: cobox_s3Qz, CO: _N, CO: _N, $dSemigroupoid_X3SC, $dSemigroupoid_X3SE, $dNearRingWithoutId_s3QE, $dNearRingWithoutId_s3QF, $dEq_s3QG] Actual args: [TYPE: Int, TYPE: Int, TYPE: Int, TYPE: Int, TYPE: Int, TYPE: Int, TYPE: Int, CO: _N, CO: _N, CO: _N, CO: (CatT D:R:CatParamProduct[0] ((CatSrc D:R:CatParamProduct[0] _N)_N ; D:R:CatSrcBasicProductSemigroup_1[0] _N _N) ((CatDest D:R:CatParamProduct[0] _N)_N ; D:R:CatDestBasicProductSemigroup_1[0] _N _N))_N ; D:R:CatTBasicProductSemigroup__1[0] _N <()>_N <()>_N, CO: (CatT D:R:CatParamProduct[0] ((CatSrc D:R:CatParamProduct[0] _N)_N ; D:R:CatSrcBasicProductSemigroup_1[0] _N _N) ((CatDest D:R:CatParamProduct[0] _N)_N ; D:R:CatDestBasicProductSemigroup_1[0] _N _N))_N ; D:R:CatTBasicProductSemigroup__1[0] _N <()>_N <()>_N, CO: (CatT D:R:CatParamSum[0] ((CatSrc D:R:CatParamSum[0] _N)_N ; D:R:CatSrcBasicSumSemigroup_1[0] _N _N) ((CatDest D:R:CatParamSum[0] _N)_N ; D:R:CatDestBasicSumSemigroup_1[0] _N _N))_N ; D:R:CatTBasicSumSemigroup__1[0] _N <()>_N <()>_N, CO: (CatT D:R:CatParamSum[0] ((CatSrc D:R:CatParamSum[0] _N)_N ; D:R:CatSrcBasicSumSemigroup_1[0] _N _N) ((CatDest D:R:CatParamSum[0] _N)_N ; D:R:CatDestBasicSumSemigroup_1[0] _N _N))_N ; D:R:CatTBasicSumSemigroup__1[0] _N <()>_N <()>_N, CO: (CatT D:R:CatParamProduct[0] ((CatSrc D:R:CatParamProduct[0] _N)_N ; D:R:CatSrcBasicProductSemigroup_1[0] _N _N) ((CatDest D:R:CatParamProduct[0] _N)_N ; D:R:CatDestBasicProductSemigroup_1[0] _N _N))_N ; D:R:CatTBasicProductSemigroup__1[0] _N <()>_N <()>_N, CO: (CatSrc D:R:CatParamSum[0] _N)_N ; D:R:CatSrcBasicSumSemigroup_1[0] _N _N ; Sym (D:R:CatDestBasicSumSemigroup_1[0] _N _N) ; (CatDest (Sym D:R:CatParamSum[0]) _N)_N, CO: (RightDistrib ((RingParamFromProduct D:R:CatParamProduct[0])_N ; D:R:RingParamFromProductBasicProductSemigroup[0]) ((LeftDistrib ((RingParamFromProduct D:R:CatParamProduct[0])_N ; D:R:RingParamFromProductBasicProductSemigroup[0]) ((CatDest D:R:CatParamProduct[0] _N)_N ; D:R:CatDestBasicProductSemigroup_1[0] _N _N) _N)_N ; D:R:LeftDistribTestInt__1[0] <()>_N _N) _N)_N ; D:R:RightDistribTestInt__1[0] <()>_N _N ; Sym (D:R:LeftDistribTestInt__1[0] <()>_N _N) ; (LeftDistrib (Sym D:R:RingParamFromProductBasicProductSemigroup[0] ; (RingParamFromProduct (Sym D:R:CatParamProduct[0]))_N) (Sym (D:R:CatDestBasicProductSemigroup_1[0] _N _N) ; (CatDest (Sym D:R:CatParamProduct[0]) _N)_N) _N)_N, CO: (CatDest D:R:CatParamProduct[0] _N)_N ; D:R:CatDestBasicProductSemigroup_1[0] _N _N ; Sym (D:R:RightDistribTestInt__1[0] <()>_N _N) ; (RightDistrib (Sym D:R:RingParamFromProductBasicProductSemigroup[0] ; (RingParamFromProduct (Sym D:R:CatParamProduct[0]))_N) (Sym (D:R:LeftDistribTestInt__1[0] <()>_N _N) ; (LeftDistrib (Sym D:R:RingParamFromProductBasicProductSemigroup[0] ; (RingParamFromProduct (Sym D:R:CatParamProduct[0]))_N) (Sym (D:R:CatDestBasicProductSemigroup_1[0] _N _N) ; (CatDest (Sym D:R:CatParamProduct[0]) _N)_N) _N)_N) _N)_N, CO: (RightDistrib ((RingParamFromProduct D:R:CatParamProduct[0])_N ; D:R:RingParamFromProductBasicProductSemigroup[0]) ((LeftDistrib ((RingParamFromProduct D:R:CatParamProduct[0])_N ; D:R:RingParamFromProductBasicProductSemigroup[0]) ((CatSrc D:R:CatParamProduct[0] _N)_N ; D:R:CatSrcBasicProductSemigroup_1[0] _N _N) _N)_N ; D:R:LeftDistribTestInt__1[0] <()>_N _N) _N)_N ; D:R:RightDistribTestInt__1[0] <()>_N _N ; Sym (D:R:LeftDistribTestInt__1[0] <()>_N _N) ; (LeftDistrib (Sym D:R:RingParamFromProductBasicProductSemigroup[0] ; (RingParamFromProduct (Sym D:R:CatParamProduct[0]))_N) (Sym (D:R:CatSrcBasicProductSemigroup_1[0] _N _N) ; (CatSrc (Sym D:R:CatParamProduct[0]) _N)_N) _N)_N, CO: (CatSrc D:R:CatParamProduct[0] _N)_N ; D:R:CatSrcBasicProductSemigroup_1[0] _N _N ; Sym (D:R:RightDistribTestInt__1[0] <()>_N _N) ; (RightDistrib (Sym D:R:RingParamFromProductBasicProductSemigroup[0] ; (RingParamFromProduct (Sym D:R:CatParamProduct[0]))_N) (Sym (D:R:LeftDistribTestInt__1[0] <()>_N _N) ; (LeftDistrib (Sym D:R:RingParamFromProductBasicProductSemigroup[0] ; (RingParamFromProduct (Sym D:R:CatParamProduct[0]))_N) (Sym (D:R:CatSrcBasicProductSemigroup_1[0] _N _N) ; (CatSrc (Sym D:R:CatParamProduct[0]) _N)_N) _N)_N) _N)_N, CO: _N, CO: (CatSrc D:R:CatParamProduct[0] _N)_N ; D:R:CatSrcBasicProductSemigroup_1[0] _N _N ; Sym (D:R:CatDestBasicProductSemigroup_1[0] _N _N) ; (CatDest (Sym D:R:CatParamProduct[0]) _N)_N, CO: _N, CO: (CatT D:R:CatParamProduct[0] ((CatSrc D:R:CatParamProduct[0] _N)_N ; D:R:CatSrcBasicProductSemigroup_1[0] _N _N) ((CatDest D:R:CatParamProduct[0] _N)_N ; D:R:CatDestBasicProductSemigroup_1[0] _N _N))_N ; D:R:CatTBasicProductSemigroup__1[0] _N <()>_N <()>_N, CO: _N, CO: _N, CO: _N, CO: (RightDistrib ((RingParamFromProduct D:R:CatParamProduct[0])_N ; D:R:RingParamFromProductBasicProductSemigroup[0]) ((LeftDistrib ((RingParamFromProduct D:R:CatParamProduct[0])_N ; D:R:RingParamFromProductBasicProductSemigroup[0]) ((CatDest D:R:CatParamProduct[0] _N)_N ; D:R:CatDestBasicProductSemigroup_1[0] _N _N) _N)_N ; D:R:LeftDistribTestInt__1[0] <()>_N _N) _N)_N ; D:R:RightDistribTestInt__1[0] <()>_N _N ; Sym (D:R:LeftDistribTestInt__1[0] <()>_N _N) ; (LeftDistrib (Sym D:R:RingParamFromProductBasicProductSemigroup[0] ; (RingParamFromProduct (Sym D:R:CatParamProduct[0]))_N) (Sym (D:R:CatDestBasicProductSemigroup_1[0] _N _N) ; (CatDest (Sym D:R:CatParamProduct[0]) _N)_N) _N)_N, CO: (CatDest D:R:CatParamProduct[0] _N)_N ; D:R:CatDestBasicProductSemigroup_1[0] _N _N ; Sym (D:R:RightDistribTestInt__1[0] <()>_N _N) ; (RightDistrib (Sym D:R:RingParamFromProductBasicProductSemigroup[0] ; (RingParamFromProduct (Sym D:R:CatParamProduct[0]))_N) (Sym (D:R:LeftDistribTestInt__1[0] <()>_N _N) ; (LeftDistrib (Sym D:R:RingParamFromProductBasicProductSemigroup[0] ; (RingParamFromProduct (Sym D:R:CatParamProduct[0]))_N) (Sym (D:R:CatDestBasicProductSemigroup_1[0] _N _N) ; (CatDest (Sym D:R:CatParamProduct[0]) _N)_N) _N)_N) _N)_N, CO: (RightDistrib ((RingParamFromProduct D:R:CatParamProduct[0])_N ; D:R:RingParamFromProductBasicProductSemigroup[0]) ((LeftDistrib ((RingParamFromProduct D:R:CatParamProduct[0])_N ; D:R:RingParamFromProductBasicProductSemigroup[0]) ((CatSrc D:R:CatParamProduct[0] _N)_N ; D:R:CatSrcBasicProductSemigroup_1[0] _N _N) _N)_N ; D:R:LeftDistribTestInt__1[0] <()>_N _N) _N)_N ; D:R:RightDistribTestInt__1[0] <()>_N _N ; Sym (D:R:LeftDistribTestInt__1[0] <()>_N _N) ; (LeftDistrib (Sym D:R:RingParamFromProductBasicProductSemigroup[0] ; (RingParamFromProduct (Sym D:R:CatParamProduct[0]))_N) (Sym (D:R:CatSrcBasicProductSemigroup_1[0] _N _N) ; (CatSrc (Sym D:R:CatParamProduct[0]) _N)_N) _N)_N, CO: (CatSrc D:R:CatParamProduct[0] _N)_N ; D:R:CatSrcBasicProductSemigroup_1[0] _N _N ; Sym (D:R:RightDistribTestInt__1[0] <()>_N _N) ; (RightDistrib (Sym D:R:RingParamFromProductBasicProductSemigroup[0] ; (RingParamFromProduct (Sym D:R:CatParamProduct[0]))_N) (Sym (D:R:LeftDistribTestInt__1[0] <()>_N _N) ; (LeftDistrib (Sym D:R:RingParamFromProductBasicProductSemigroup[0] ; (RingParamFromProduct (Sym D:R:CatParamProduct[0]))_N) (Sym (D:R:CatSrcBasicProductSemigroup_1[0] _N _N) ; (CatSrc (Sym D:R:CatParamProduct[0]) _N)_N) _N)_N) _N)_N, CO: (RightDistrib ((RingParamFromProduct D:R:CatParamProduct[0])_N ; D:R:RingParamFromProductBasicProductSemigroup[0]) ((LeftDistrib ((RingParamFromProduct D:R:CatParamProduct[0])_N ; D:R:RingParamFromProductBasicProductSemigroup[0]) ((CatDest D:R:CatParamProduct[0] _N)_N ; D:R:CatDestBasicProductSemigroup_1[0] _N _N) _N)_N ; D:R:LeftDistribTestInt__1[0] <()>_N _N) _N)_N ; D:R:RightDistribTestInt__1[0] <()>_N _N ; Sym (D:R:LeftDistribTestInt__1[0] <()>_N _N) ; (LeftDistrib (Sym D:R:RingParamFromProductBasicProductSemigroup[0] ; (RingParamFromProduct (Sym D:R:CatParamProduct[0]))_N) (Sym (D:R:CatDestBasicProductSemigroup_1[0] _N _N) ; (CatDest (Sym D:R:CatParamProduct[0]) _N)_N) _N)_N, CO: (CatDest D:R:CatParamProduct[0] _N)_N ; D:R:CatDestBasicProductSemigroup_1[0] _N _N ; Sym (D:R:RightDistribTestInt__1[0] <()>_N _N) ; (RightDistrib (Sym D:R:RingParamFromProductBasicProductSemigroup[0] ; (RingParamFromProduct (Sym D:R:CatParamProduct[0]))_N) (Sym (D:R:LeftDistribTestInt__1[0] <()>_N _N) ; (LeftDistrib (Sym D:R:RingParamFromProductBasicProductSemigroup[0] ; (RingParamFromProduct (Sym D:R:CatParamProduct[0]))_N) (Sym (D:R:CatDestBasicProductSemigroup_1[0] _N _N) ; (CatDest (Sym D:R:CatParamProduct[0]) _N)_N) _N)_N) _N)_N, CO: (RightDistrib ((RingParamFromProduct D:R:CatParamProduct[0])_N ; D:R:RingParamFromProductBasicProductSemigroup[0]) ((LeftDistrib ((RingParamFromProduct D:R:CatParamProduct[0])_N ; D:R:RingParamFromProductBasicProductSemigroup[0]) ((CatSrc D:R:CatParamProduct[0] _N)_N ; D:R:CatSrcBasicProductSemigroup_1[0] _N _N) _N)_N ; D:R:LeftDistribTestInt__1[0] <()>_N _N) _N)_N ; D:R:RightDistribTestInt__1[0] <()>_N _N ; Sym (D:R:LeftDistribTestInt__1[0] <()>_N _N) ; (LeftDistrib (Sym D:R:RingParamFromProductBasicProductSemigroup[0] ; (RingParamFromProduct (Sym D:R:CatParamProduct[0]))_N) (Sym (D:R:CatSrcBasicProductSemigroup_1[0] _N _N) ; (CatSrc (Sym D:R:CatParamProduct[0]) _N)_N) _N)_N, CO: (CatSrc D:R:CatParamProduct[0] _N)_N ; D:R:CatSrcBasicProductSemigroup_1[0] _N _N ; Sym (D:R:RightDistribTestInt__1[0] <()>_N _N) ; (RightDistrib (Sym D:R:RingParamFromProductBasicProductSemigroup[0] ; (RingParamFromProduct (Sym D:R:CatParamProduct[0]))_N) (Sym (D:R:LeftDistribTestInt__1[0] <()>_N _N) ; (LeftDistrib (Sym D:R:RingParamFromProductBasicProductSemigroup[0] ; (RingParamFromProduct (Sym D:R:CatParamProduct[0]))_N) (Sym (D:R:CatSrcBasicProductSemigroup_1[0] _N _N) ; (CatSrc (Sym D:R:CatParamProduct[0]) _N)_N) _N)_N) _N)_N, CO: (CatT D:R:CatParamProduct[0] ((CatDest D:R:CatParamProduct[0] _N)_N ; D:R:CatDestBasicProductSemigroup_1[0] _N _N) ((CatDest D:R:CatParamProduct[0] _N)_N ; D:R:CatDestBasicProductSemigroup_1[0] _N _N))_N ; D:R:CatTBasicProductSemigroup__1[0] _N <()>_N <()>_N, CO: _N, CO: (CatT D:R:CatParamProduct[0] ((CatSrc D:R:CatParamProduct[0] _N)_N ; D:R:CatSrcBasicProductSemigroup_1[0] _N _N) ((CatDest D:R:CatParamProduct[0] _N)_N ; D:R:CatDestBasicProductSemigroup_1[0] _N _N))_N ; D:R:CatTBasicProductSemigroup__1[0] _N <()>_N <()>_N, CO: _N, CO: _N, CO: _N, CO: (CatT D:R:CatParamSum[0] ((CatDest D:R:CatParamSum[0] _N)_N ; D:R:CatDestBasicSumSemigroup_1[0] _N _N) ((CatDest D:R:CatParamSum[0] _N)_N ; D:R:CatDestBasicSumSemigroup_1[0] _N _N))_N ; D:R:CatTBasicSumSemigroup__1[0] _N <()>_N <()>_N, CO: (CatSrc D:R:CatParamSum[0] _N)_N ; D:R:CatSrcBasicSumSemigroup_1[0] _N _N ; Sym (D:R:CatDestBasicSumSemigroup_1[0] _N _N) ; (CatDest (Sym D:R:CatParamSum[0]) _N)_N, CO: (CatT D:R:CatParamSum[0] ((CatSrc D:R:CatParamSum[0] _N)_N ; D:R:CatSrcBasicSumSemigroup_1[0] _N _N) ((CatDest D:R:CatParamSum[0] _N)_N ; D:R:CatDestBasicSumSemigroup_1[0] _N _N))_N ; D:R:CatTBasicSumSemigroup__1[0] _N <()>_N <()>_N, CO: _N, CO: _N, CO: _N, CO: _N, CO: _N, CO: (CatT D:R:CatParamSum[0] ((CatDest D:R:CatParamSum[0] _N)_N ; D:R:CatDestBasicSumSemigroup_1[0] _N _N) ((CatDest D:R:CatParamSum[0] _N)_N ; D:R:CatDestBasicSumSemigroup_1[0] _N _N))_N ; D:R:CatTBasicSumSemigroup__1[0] _N <()>_N <()>_N, CO: _N, CO: (CatT D:R:CatParamSum[0] ((CatSrc D:R:CatParamSum[0] _N)_N ; D:R:CatSrcBasicSumSemigroup_1[0] _N _N) ((CatDest D:R:CatParamSum[0] _N)_N ; D:R:CatDestBasicSumSemigroup_1[0] _N _N))_N ; D:R:CatTBasicSumSemigroup__1[0] _N <()>_N <()>_N, CO: _N, CO: _N, CO: _N, CO: _N, CO: (CatT D:R:CatParamProduct[0] ((CatSrc D:R:CatParamProduct[0] _N)_N ; D:R:CatSrcBasicProductSemigroup_1[0] _N _N) ((CatDest D:R:CatParamProduct[0] _N)_N ; D:R:CatDestBasicProductSemigroup_1[0] _N _N))_N ; D:R:CatTBasicProductSemigroup__1[0] _N <()>_N <()>_N, CO: _N, CO: _N, ($c._a32V @ Int $fNumInt) `cast` (Sym (N:Semigroupoid[0] _N) ; (Semigroupoid (Sym D:R:CatParamSum[0]))_R :: ((forall catAB_awI[sk] catBC_awJ[sk] catAC_awK[sk] a_awL[sk] b_awM[sk] c_awN[sk]. ((BasicSumSemigroup Int :: *) ~ (CatParam catAB_awI[sk] :: *), (BasicSumSemigroup Int :: *) ~ (CatParam catBC_awJ[sk] :: *), (BasicSumSemigroup Int :: *) ~ (CatParam catAC_awK[sk] :: *), (a_awL[sk] :: *) ~ (CatSrc (BasicSumSemigroup Int) catAB_awI[sk] :: *), (b_awM[sk] :: *) ~ (CatSrc (BasicSumSemigroup Int) catBC_awJ[sk] :: *), (a_awL[sk] :: *) ~ (CatSrc (BasicSumSemigroup Int) catAC_awK[sk] :: *), (b_awM[sk] :: *) ~ (CatDest (BasicSumSemigroup Int) catAB_awI[sk] :: *), (c_awN[sk] :: *) ~ (CatDest (BasicSumSemigroup Int) catBC_awJ[sk] :: *), (c_awN[sk] :: *) ~ (CatDest (BasicSumSemigroup Int) catAC_awK[sk] :: *), (catAB_awI[sk] :: *) ~ (CatT (BasicSumSemigroup Int) a_awL[sk] b_awM[sk] :: *), (catBC_awJ[sk] :: *) ~ (CatT (BasicSumSemigroup Int) b_awM[sk] c_awN[sk] :: *), (catAC_awK[sk] :: *) ~ (CatT (BasicSumSemigroup Int) a_awL[sk] c_awN[sk] :: *)) => catBC_awJ[sk] -> catAB_awI[sk] -> catAC_awK[sk]) :: *) ~R# (Semigroupoid (CatParam (Sum Int)) :: Constraint)), ($c._a32m @ Int $fNumInt) `cast` (Sym (N:Semigroupoid[0] _N) ; (Semigroupoid (Sym D:R:CatParamProduct[0]))_R :: ((forall catAB_awI[sk] catBC_awJ[sk] catAC_awK[sk] a_awL[sk] b_awM[sk] c_awN[sk]. ((BasicProductSemigroup Int :: *) ~ (CatParam catAB_awI[sk] :: *), (BasicProductSemigroup Int :: *) ~ (CatParam catBC_awJ[sk] :: *), (BasicProductSemigroup Int :: *) ~ (CatParam catAC_awK[sk] :: *), (a_awL[sk] :: *) ~ (CatSrc (BasicProductSemigroup Int) catAB_awI[sk] :: *), (b_awM[sk] :: *) ~ (CatSrc (BasicProductSemigroup Int) catBC_awJ[sk] :: *), (a_awL[sk] :: *) ~ (CatSrc (BasicProductSemigroup Int) catAC_awK[sk] :: *), (b_awM[sk] :: *) ~ (CatDest (BasicProductSemigroup Int) catAB_awI[sk] :: *), (c_awN[sk] :: *) ~ (CatDest (BasicProductSemigroup Int) catBC_awJ[sk] :: *), (c_awN[sk] :: *) ~ (CatDest (BasicProductSemigroup Int) catAC_awK[sk] :: *), (catAB_awI[sk] :: *) ~ (CatT (BasicProductSemigroup Int) a_awL[sk] b_awM[sk] :: *), (catBC_awJ[sk] :: *) ~ (CatT (BasicProductSemigroup Int) b_awM[sk] c_awN[sk] :: *), (catAC_awK[sk] :: *) ~ (CatT (BasicProductSemigroup Int) a_awL[sk] c_awN[sk] :: *)) => catBC_awJ[sk] -> catAB_awI[sk] -> catAC_awK[sk]) :: *) ~R# (Semigroupoid (CatParam (Product Int)) :: Constraint)), $fNearRingWithoutIdTestInt `cast` ((NearRingWithoutId (Sym D:R:RingParamFromSumBasicSumSemigroup[0] ; (RingParamFromSum (Sym D:R:CatParamSum[0]))_N))_R :: (NearRingWithoutId TestInt :: Constraint) ~R# (NearRingWithoutId (RingParamFromSum (CatParam (Sum Int))) :: Constraint)), $fNearRingWithoutIdTestInt `cast` ((NearRingWithoutId (Sym D:R:RingParamFromProductBasicProductSemigroup[0] ; (RingParamFromProduct (Sym D:R:CatParamProduct[0]))_N))_R :: (NearRingWithoutId TestInt :: Constraint) ~R# (NearRingWithoutId (RingParamFromProduct (CatParam (Product Int))) :: Constraint)), $fEqInt, x, x, x] 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 Jul 19 06:40:03 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 19 Jul 2016 06:40:03 -0000 Subject: [GHC] #12408: "ghc: panic! (the 'impossible' happened)" only when compiled with "-O" In-Reply-To: <046.d29ea653b6a5476c1904e0cd28bb26ab@haskell.org> References: <046.d29ea653b6a5476c1904e0cd28bb26ab@haskell.org> Message-ID: <061.dffac47de1c946b6fd4d279e652b0ad2@haskell.org> #12408: "ghc: panic! (the 'impossible' happened)" only when compiled with "-O" -------------------------------------+------------------------------------- Reporter: clinton | Owner: 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 | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by clinton): * Attachment "ring_bug.hs" added. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 19 06:40:21 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 19 Jul 2016 06:40:21 -0000 Subject: [GHC] #12408: "ghc: panic! (the 'impossible' happened)" only when compiled with "-O" In-Reply-To: <046.d29ea653b6a5476c1904e0cd28bb26ab@haskell.org> References: <046.d29ea653b6a5476c1904e0cd28bb26ab@haskell.org> Message-ID: <061.f513091f193f1eabc4b62cb2ea70f1e1@haskell.org> #12408: "ghc: panic! (the 'impossible' happened)" only when compiled with "-O" -------------------------------------+------------------------------------- Reporter: clinton | Owner: 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 | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by clinton): * Attachment "error.txt" added. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 19 07:57:31 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 19 Jul 2016 07:57:31 -0000 Subject: [GHC] #12357: Increasing maximum constraint tuple size significantly blows up compiler allocations In-Reply-To: <046.dd0f12e974ac3c5c9febd70397bf4138@haskell.org> References: <046.dd0f12e974ac3c5c9febd70397bf4138@haskell.org> Message-ID: <061.e49530dde8a3519fcc9d6ddee8b417aa@haskell.org> #12357: Increasing maximum constraint tuple size significantly blows up compiler allocations -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.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:D2400 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * differential: => Phab:D2400 Comment: Phab:D2400 is also relevant here as it reworks the commit mentioned in comment:18. However, there is further change afoot: On Skype Simon and I discussed the current situation and agreed that it's still not quite right. He has summarized the conclusion on Phab:D2400, > On skype we agreed that > > - the the TcIface path doesn't need to even try to look for tuple names because they are encoded specially in interface files. We only need parse tuple names specially in the template haskell route. > > - We'll put cons and nil and other special cases into the OriginalNameCache so we don't need to parse them specially here; fewer special cases. > The point is that we needn't worry about the cost of including things like `(:)` and `[]` in the name cache, so we should just remove their cases from `isBuiltInOcc_maybe` and handle them in the usual way. The only cases which we should handle in `isBuiltInOcc_maybe` are those of tuples (of boxed, unboxed, and constraint varieties) and eventually unboxed sums. Additionally Simon proposed that we break up `lookupOrigNameCache` into two variants (names up for debate), * `lookupOrigNameCache'`, which will merely lookup an `OccName` in the name cache, without attempting to resolve built-in syntax (with an assert verifying that we aren't looking up something in `GHC.Tuple`, as definitions defined there aren't in the name cache) * `lookupOrigNameCache`, which will lookup an `OccName` as above, but also attempt to parse out names corresponding to built-in syntax. Then we can use `lookupOrigNameCache'` in the `ReadIface` codepaths, where we know that we should never see built-in syntax (since these names are encoded specially in the interface file symbol table, see `Note [Symbol table representation of names]` in `BinIface`). In the Template Haskell codepaths, it will still be necessary to use `lookupOrigNameCache`, to ensure that things like `mkName "(,)"` work. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 19 08:22:12 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 19 Jul 2016 08:22:12 -0000 Subject: [GHC] #12367: Commit adding instances to GHC.Generics regression compiler performance In-Reply-To: <046.87a5f8a842934b4554eedf79fb6bebbc@haskell.org> References: <046.87a5f8a842934b4554eedf79fb6bebbc@haskell.org> Message-ID: <061.8bbd044b850cc5f7be70af29c2cfbd36@haskell.org> #12367: Commit adding instances to GHC.Generics regression compiler performance -------------------------------------+------------------------------------- Reporter: bgamari | Owner: bgamari Type: bug | Status: patch Priority: normal | Milestone: 8.0.2 Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Generics 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:D2411 Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): Patch looks good. I have commented it. I don't understand why `relevantBindings` would pull in anything. What "surrounding comments"? Do you know why it pulls `GHC.Generics` in? Worth understanding... -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 19 08:22:43 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 19 Jul 2016 08:22:43 -0000 Subject: [GHC] #12357: Increasing maximum constraint tuple size significantly blows up compiler allocations In-Reply-To: <046.dd0f12e974ac3c5c9febd70397bf4138@haskell.org> References: <046.dd0f12e974ac3c5c9febd70397bf4138@haskell.org> Message-ID: <061.cad26825c00edbacb31eb2f11dd97f34@haskell.org> #12357: Increasing maximum constraint tuple size significantly blows up compiler allocations -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.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:D2400 Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): In comment:21 I described the plan. Now I'll describe the reality, which includes a few wrinkles. As it turns out, we actually **do** include almost all of the tuple types in the original name cache. We can see this by noticing that `newHscEnv` initializes the namecache as `(initNameCache us allKnownKeyNames)`, where `allKnownKeyNames` includes, {{{#!hs knownKeyNames = concat [ ... , concatMap tycon_kk_names typeNatTyCons , concatMap (tycon_kk_names . tupleTyCon Boxed) [2..mAX_TUPLE_SIZE] -- Yuk , cTupleTyConNames , ... ] allKnownKeyNames = knownKeyNames ++ ... }}} Consequently, if you remove the `isBuiltInOcc_maybe` checks entirely things //almost// continue to work; almost because you will note that unboxed tuples are missing. This had led me to assume that all tuples were missing from the name cache. However, if you add unboxed tuples to `knownKeyNames` things validate without any trouble. So, the question now is whether we want to change this by removing tuples from the original name cache. To answer this let's consider what this would entail: I believe the only sensible way to implement comment:21 would be to filter out tuples from `allKnownKeyNames` when initializing the name cache. I specifically do not propose to remove tuples from `allKnownKeysNames` since the `TcTypeable` implementation relies on them being present so it knows to generate type representations for them. Is filtering them out worthwhile? I'll try to take some measurements to find out, but I'm not entirely convinced (at least for tuples; unboxed sums may be another story). -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 19 08:36:10 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 19 Jul 2016 08:36:10 -0000 Subject: [GHC] #12357: Increasing maximum constraint tuple size significantly blows up compiler allocations In-Reply-To: <046.dd0f12e974ac3c5c9febd70397bf4138@haskell.org> References: <046.dd0f12e974ac3c5c9febd70397bf4138@haskell.org> Message-ID: <061.5a7272c6f8a3567487ebbf4c8b08edbd@haskell.org> #12357: Increasing maximum constraint tuple size significantly blows up compiler allocations -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.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:D2400 Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): Why/how does the `TcTypeable` impl rely on them being there??? There jolly well ought to be a comment to say so. All I see is * `knownKeyNames` used in building `knownKeyNamesMap` in `BinIface`. Waste of time having tuples in there because they are treated specially by `BinIface`. * Initialising the name cache in `HscMain`. And that's really it. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 19 08:44:59 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 19 Jul 2016 08:44:59 -0000 Subject: [GHC] #12409: Unboxed tuples have no type representations Message-ID: <046.32a785a6183ec0ab7732a4ef59760aa4@haskell.org> #12409: Unboxed tuples have no type representations -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: bug | Status: new Priority: normal | Milestone: 8.0.2 Component: Compiler | Version: 8.0.1 Keywords: typeable | 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 ticket continues with the long tradition of types missing type representations (see #12082, #12132, #11120). This time the culprit is unboxed tuples, {{{ $ ghci GHCi, version 8.0.1: http://www.haskell.org/ghc/ :? for help Loaded GHCi configuration from /home/ben/.ghci λ> import Data.Typeable λ> :set -XUnboxedTuples λ> typeRep (Proxy :: Proxy (#Int, Int#)) ghc: panic! (the 'impossible' happened) (GHC version 8.0.1 for x86_64-unknown-linux): tyConRep (#,#) Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug }}} The problem, as usual, is that the tycons are missing from `knownKeyNames`. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 19 08:46:06 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 19 Jul 2016 08:46:06 -0000 Subject: [GHC] #12132: Type representations missing for promoted boxed tuples In-Reply-To: <046.73dbaf7b6ca62d79018b512a7b0731f6@haskell.org> References: <046.73dbaf7b6ca62d79018b512a7b0731f6@haskell.org> Message-ID: <061.b867d7ca681878f5d0425e0c7588f363@haskell.org> #12132: Type representations missing for promoted boxed tuples -------------------------------------+------------------------------------- Reporter: bgamari | Owner: bgamari Type: bug | Status: closed Priority: normal | Milestone: 8.0.2 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): Phab:D2279 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: merge => closed * resolution: => fixed Comment: Merged to `ghc-8.0` as f7b6adccec14cd4d8d4854e01b9f78b80f533b4d. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 19 08:46:39 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 19 Jul 2016 08:46:39 -0000 Subject: [GHC] #12409: Unboxed tuples have no type representations In-Reply-To: <046.32a785a6183ec0ab7732a4ef59760aa4@haskell.org> References: <046.32a785a6183ec0ab7732a4ef59760aa4@haskell.org> Message-ID: <061.d5b88452d02f557021ea57e5c8e95e24@haskell.org> #12409: Unboxed tuples have no type representations -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: bug | Status: new Priority: normal | Milestone: 8.0.2 Component: Compiler | Version: 8.0.1 Resolution: | Keywords: typeable 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 does it matter that they are not in `knownKeyNames`? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 19 08:50:36 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 19 Jul 2016 08:50:36 -0000 Subject: [GHC] #12357: Increasing maximum constraint tuple size significantly blows up compiler allocations In-Reply-To: <046.dd0f12e974ac3c5c9febd70397bf4138@haskell.org> References: <046.dd0f12e974ac3c5c9febd70397bf4138@haskell.org> Message-ID: <061.10b2fa12a228ff800d33e5544850f38b@haskell.org> #12357: Increasing maximum constraint tuple size significantly blows up compiler allocations -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.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:D2400 Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): Hmm, while purusing I stumbled upon this comment in `TysWiredIn`, {{{ wiredInTyCons = [ unitTyCon -- Not treated like other tuples, because -- it's defined in GHC.Base, and there's only -- one of it. We put it in wiredInTyCons so -- that it'll pre-populate the name cache, so -- the special case in lookupOrigNameCache -- doesn't need to look out for it , ... }}} Which could be interpreted to imply that `wiredInTyCons`, not `allKnownKeyTyCons`, should be used to initialize the original name cache. Was this intentional or just me reading too much into the language? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 19 08:50:40 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 19 Jul 2016 08:50:40 -0000 Subject: [GHC] #12132: Type representations missing for promoted boxed tuples In-Reply-To: <046.73dbaf7b6ca62d79018b512a7b0731f6@haskell.org> References: <046.73dbaf7b6ca62d79018b512a7b0731f6@haskell.org> Message-ID: <061.ba8f6514316e845ea95d38616ea9a8ad@haskell.org> #12132: Type representations missing for promoted boxed tuples -------------------------------------+------------------------------------- Reporter: bgamari | Owner: bgamari Type: bug | Status: closed Priority: normal | Milestone: 8.0.2 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): Phab:D2279 Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): mmm. So it looks as though ''promoted'' tuple data cons are not handled by the special encoding in `Note [Symbol table representation of names]` in `BinIface`. Adding them to `knownKeyNames` may be one solution. But another, and a more consistent one, is to fix up the encoding described in that Note so that it does handle promoted tuple data cons. Let's not have several different fixes for the same problem! -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 19 08:53:17 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 19 Jul 2016 08:53:17 -0000 Subject: [GHC] #12357: Increasing maximum constraint tuple size significantly blows up compiler allocations In-Reply-To: <046.dd0f12e974ac3c5c9febd70397bf4138@haskell.org> References: <046.dd0f12e974ac3c5c9febd70397bf4138@haskell.org> Message-ID: <061.7a31d392b89de1c3e02522a81bd68c62@haskell.org> #12357: Increasing maximum constraint tuple size significantly blows up compiler allocations -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.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:D2400 Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): This all dates from when tuples were not in the original name cache (and I think they should indeed not be). But we made a special case for the unit tuple; I forget why, and it probably doesn't matter much. No, we must initialise the cache will all known-key tycons (tuples aside) otherwise, well, we won't assign the right known key to one of them. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 19 09:12:31 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 19 Jul 2016 09:12:31 -0000 Subject: [GHC] #12132: Type representations missing for promoted boxed tuples In-Reply-To: <046.73dbaf7b6ca62d79018b512a7b0731f6@haskell.org> References: <046.73dbaf7b6ca62d79018b512a7b0731f6@haskell.org> Message-ID: <061.1e353a97e0eca4a5e0f87b2ab1d64d5b@haskell.org> #12132: Type representations missing for promoted boxed tuples -------------------------------------+------------------------------------- Reporter: bgamari | Owner: bgamari Type: bug | Status: closed Priority: normal | Milestone: 8.0.2 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): Phab:D2279 Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): > Adding them to knownKeyNames may be one solution. But another, and a more consistent one, is to fix up the encoding described in that Note so that it does handle promoted tuple data cons. Let's not have several different fixes for the same problem! Sure, sounds like a better plan. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 19 09:21:47 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 19 Jul 2016 09:21:47 -0000 Subject: [GHC] #12409: Unboxed tuples have no type representations In-Reply-To: <046.32a785a6183ec0ab7732a4ef59760aa4@haskell.org> References: <046.32a785a6183ec0ab7732a4ef59760aa4@haskell.org> Message-ID: <061.ab6452a3b56ee55c4ff1d52d8dad68df@haskell.org> #12409: Unboxed tuples have no type representations -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: bug | Status: new Priority: normal | Milestone: 8.0.2 Component: Compiler | Version: 8.0.1 Resolution: | Keywords: typeable Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- @@ -18,2 +18,1 @@ - The problem, as usual, is that the tycons are missing from - `knownKeyNames`. + The problem, as usual, is that the tycons are missing from `primTyCons`. New description: This ticket continues with the long tradition of types missing type representations (see #12082, #12132, #11120). This time the culprit is unboxed tuples, {{{ $ ghci GHCi, version 8.0.1: http://www.haskell.org/ghc/ :? for help Loaded GHCi configuration from /home/ben/.ghci λ> import Data.Typeable λ> :set -XUnboxedTuples λ> typeRep (Proxy :: Proxy (#Int, Int#)) ghc: panic! (the 'impossible' happened) (GHC version 8.0.1 for x86_64-unknown-linux): tyConRep (#,#) Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug }}} The problem, as usual, is that the tycons are missing from `primTyCons`. -- Comment (by bgamari): > Why does it matter that they are not in `knownKeyNames`? Sorry, I had meant `primTyCons` above. The reason is that `TcTypeable` uses `primTyCons` as the list of `TyCon`s which are defined in `GHC.Prim`. When compiling `GHC.Types` `TcTypeable` generate Typeable representations for the types in `primTyCons`. If a primitive TyCon is missing from the list then that type's `Typeable` representation will also be missing (which I believe is what happened in this bug). Ultimately we don't want to add unboxed tuples to `primTyCons` since we don't want to add them to the original name cache (as discussed in #12357). I have a proposed solution on the way. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 19 09:25:58 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 19 Jul 2016 09:25:58 -0000 Subject: [GHC] #12409: Unboxed tuples have no type representations In-Reply-To: <046.32a785a6183ec0ab7732a4ef59760aa4@haskell.org> References: <046.32a785a6183ec0ab7732a4ef59760aa4@haskell.org> Message-ID: <061.268e52d4e6b8bdb61189436cdd366d6f@haskell.org> #12409: Unboxed tuples have no type representations -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: bug | Status: new Priority: normal | Milestone: 8.0.2 Component: Compiler | Version: 8.0.1 Resolution: | Keywords: typeable 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): On further investigation, my previous hypothesis is completely wrong. The problem is that `TyCon.tyConRepName_maybe` does not handle the case of `AlgTyCon { algTcParent = UnboxedAlgTyCon }`. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 19 09:29:37 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 19 Jul 2016 09:29:37 -0000 Subject: [GHC] #12409: Unboxed tuples have no type representations In-Reply-To: <046.32a785a6183ec0ab7732a4ef59760aa4@haskell.org> References: <046.32a785a6183ec0ab7732a4ef59760aa4@haskell.org> Message-ID: <061.089da42400033977efe466bda45d64bf@haskell.org> #12409: Unboxed tuples have no type representations -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: bug | Status: new Priority: normal | Milestone: 8.0.2 Component: Compiler | Version: 8.0.1 Resolution: | Keywords: typeable 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 guess the question here is do we want unboxed tuples to be representable? It looks like it would be easy to make them representable: just add a field carrying the representation name to `UnboxedAlgTyCon` just as we do with `AlgTyCon`. If we'd prefer to keep them unrepresentable then I suppose we should make the solver throw a more polite error message. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 19 10:01:04 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 19 Jul 2016 10:01:04 -0000 Subject: [GHC] #12238: Many tests fail when BuildFlavour == perf-llvm and DYNAMIC_GHC_PROGRAMS == NO In-Reply-To: <044.4fede5f9eea8d5fff3be85b1c00e138e@haskell.org> References: <044.4fede5f9eea8d5fff3be85b1c00e138e@haskell.org> Message-ID: <059.f5564073ee3da0c295c6e2d77189d9cc@haskell.org> #12238: Many tests fail when BuildFlavour == perf-llvm and DYNAMIC_GHC_PROGRAMS == NO -----------------------------------+-------------------------------------- Reporter: erikd | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 8.1 Resolution: duplicate | Keywords: Operating System: Linux | Architecture: x86_64 (amd64) Type of failure: Other | Test Case: Blocked By: | Blocking: Related Tickets: #12230, #12169 | Differential Rev(s): Wiki Page: | -----------------------------------+-------------------------------------- Changes (by erikd): * status: new => closed * resolution: => duplicate Comment: Not sure about #12169, but 100% certain this is a duplicate of #11981. Closing this one. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 19 10:02:12 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 19 Jul 2016 10:02:12 -0000 Subject: [GHC] #11981: unknown symbol `__udivti3' when BuildFlavour = perf-llvm In-Reply-To: <044.ad3f32463aae7c699d4d4bd8ae6b6c27@haskell.org> References: <044.ad3f32463aae7c699d4d4bd8ae6b6c27@haskell.org> Message-ID: <059.3bea5ec6efad9c0427849ebb99eb456a@haskell.org> #11981: unknown symbol `__udivti3' when BuildFlavour = perf-llvm -------------------------------------+------------------------------------- Reporter: erikd | Owner: Type: bug | Status: new Priority: normal | Milestone: 8.0.2 Component: Compiler | Version: 8.1 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 erikd): The update is that this now happens with `DYNAMIC_GHC_PROGRAMS = YES`. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 19 10:13:23 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 19 Jul 2016 10:13:23 -0000 Subject: [GHC] #12367: Commit adding instances to GHC.Generics regression compiler performance In-Reply-To: <046.87a5f8a842934b4554eedf79fb6bebbc@haskell.org> References: <046.87a5f8a842934b4554eedf79fb6bebbc@haskell.org> Message-ID: <061.b333990cfeb5559dd22a978003ff0ac1@haskell.org> #12367: Commit adding instances to GHC.Generics regression compiler performance -------------------------------------+------------------------------------- Reporter: bgamari | Owner: bgamari Type: bug | Status: patch Priority: normal | Milestone: 8.0.2 Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Generics 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:D2411 Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonmar): * cc: simonmar (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 19 10:54:51 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 19 Jul 2016 10:54:51 -0000 Subject: [GHC] #12146: syntax repair suggestion is too eager to suggest TemplateHaskell In-Reply-To: <049.ae34cc16e6637ea2bb94449efc0751c9@haskell.org> References: <049.ae34cc16e6637ea2bb94449efc0751c9@haskell.org> Message-ID: <064.c23e4c3c0944b87a3f0509f80f2c3fba@haskell.org> #12146: syntax repair suggestion is too eager to suggest TemplateHaskell -------------------------------------+------------------------------------- Reporter: j.waldmann | Owner: Type: feature request | 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: #7396 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by adityadivekar): thomie: ping regarding the patch. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 19 11:20:21 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 19 Jul 2016 11:20:21 -0000 Subject: [GHC] #11981: unknown symbol `__udivti3' when BuildFlavour = perf-llvm In-Reply-To: <044.ad3f32463aae7c699d4d4bd8ae6b6c27@haskell.org> References: <044.ad3f32463aae7c699d4d4bd8ae6b6c27@haskell.org> Message-ID: <059.91bddcab49d7734587175d49e41a85e2@haskell.org> #11981: unknown symbol `__udivti3' when BuildFlavour = perf-llvm -------------------------------------+------------------------------------- Reporter: erikd | Owner: Type: bug | Status: new Priority: normal | Milestone: 8.0.2 Component: Compiler | Version: 8.1 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 erikd): Searching for this on the web and all I can find is links to implementation like https://searchcode.com/codesearch/view/29840070/ is is amazing un-informative. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 19 11:36:27 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 19 Jul 2016 11:36:27 -0000 Subject: [GHC] #12150: Compile time performance degradation on code that uses undefined/error with CallStacks In-Reply-To: <045.a0bd3502ce7a1f35f82939f7b0bb87d6@haskell.org> References: <045.a0bd3502ce7a1f35f82939f7b0bb87d6@haskell.org> Message-ID: <060.4a52b1d2a7cd34fd0c1dfbea9284cfd7@haskell.org> #12150: Compile time performance degradation on code that uses undefined/error with CallStacks -------------------------------------+------------------------------------- Reporter: thomie | Owner: Type: bug | Status: new Priority: high | Milestone: 8.0.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: #10844 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by thomie): * priority: normal => high * milestone: => 8.0.2 @@ -192,1 +192,2 @@ - subprocess.call(['ghc-8.0.1', '-v0', '-O', tempfile]) + subprocess.call(['ghc-8.0.1', '-fforce-recomp', '-v0', '-O', + tempfile]) New description: GHC 8 has a lot of trouble compiling the following program: {{{#!hs module Serialize where data Result a = Success a | Error String {- 80 guards ghc-7.10.3 -O : 0.3s ghc-8.0.1 -O : 1.8s -} instance Functor Result where {-# INLINE fmap #-} fmap | bool = f | bool = f | bool = f | bool = f | bool = f | bool = f | bool = f | bool = f | bool = f | bool = f | bool = f | bool = f | bool = f | bool = f | bool = f | bool = f | bool = f | bool = f | bool = f | bool = f | bool = f | bool = f | bool = f | bool = f | bool = f | bool = f | bool = f | bool = f | bool = f | bool = f | bool = f | bool = f | bool = f | bool = f | bool = f | bool = f | bool = f | bool = f | bool = f | bool = f | bool = f | bool = f | bool = f | bool = f | bool = f | bool = f | bool = f | bool = f | bool = f | bool = f | bool = f | bool = f | bool = f | bool = f | bool = f | bool = f | bool = f | bool = f | bool = f | bool = f | bool = f | bool = f | bool = f | bool = f | bool = f | bool = f | bool = f | bool = f | bool = f | bool = f | bool = f | bool = f | bool = f | bool = f | bool = f | bool = f | bool = f | bool = f | bool = f | bool = f where bool = undefined f = undefined }}} Here are some timing results, depending on the number of `| bool = f` clauses: {{{ * ghc-8.0.1 N clauses : time (s) 10 : 0.61 20 : 0.78 40 : 1.03 80 : 1.64 160 : 2.83 320 : 5.16 640 : 10.37 1280 : 21.16 * ghc-7.10.3 N clauses : time (s) 10 : 0.33 20 : 0.29 40 : 0.34 80 : 0.30 160 : 0.32 320 : 0.35 640 : 0.48 1280 : 0.80 }}} I think this compile time difference is caused by the `CallStack` changes introduced in GHC 8.0. When I use a version of `undefined` that doesn't have a CallStack, there is no difference in compile time when using GHC 7.10 or GHC 8.0. This is my implementation of `undefined` without `CallStack`: {{{ import GHC.Exception (errorCallException) import GHC.Prim (raise#) import Prelude (Char) error :: [Char] -> a error s = raise# (errorCallException s) undefined :: a undefined = error "undefined without callstack" }}} This is the quick and dirty Python script I used to generate those timing results (ghc version is hardcoded): {{{#!py import os import tempfile import time import subprocess def src(n): return ''' module Test where data Result a = Success a | Error String instance Functor Result where {{-# INLINE fmap #-}} fmap {0} where bool = undefined f = undefined '''.format('\n | bool = f' * n) tempfile = tempfile.mktemp('.hs') print('tempfile = {0}'.format(tempfile)) print('N clauses : time (s)') for i in range(8): n = 10 * 2 ** i with open(tempfile, 'w') as f: f.write(src(n)) f.flush() t0 = time.time() subprocess.call(['ghc-8.0.1', '-fforce-recomp', '-v0', '-O', tempfile]) t1 = time.time() print(str(n).ljust(10) + ': %.2f' % (t1 - t0)) os.remove(tempfile) }}} -- -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 19 12:47:53 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 19 Jul 2016 12:47:53 -0000 Subject: [GHC] #12150: Compile time performance degradation on code that uses undefined/error with CallStacks In-Reply-To: <045.a0bd3502ce7a1f35f82939f7b0bb87d6@haskell.org> References: <045.a0bd3502ce7a1f35f82939f7b0bb87d6@haskell.org> Message-ID: <060.5e28b510d3373ca278f61f08d525b22e@haskell.org> #12150: Compile time performance degradation on code that uses undefined/error with CallStacks -------------------------------------+------------------------------------- Reporter: thomie | Owner: Type: bug | Status: new Priority: high | Milestone: 8.0.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: #10844 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): Eric, might you have time to look at this? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 19 12:51:24 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 19 Jul 2016 12:51:24 -0000 Subject: [GHC] #12150: Compile time performance degradation on code that uses undefined/error with CallStacks In-Reply-To: <045.a0bd3502ce7a1f35f82939f7b0bb87d6@haskell.org> References: <045.a0bd3502ce7a1f35f82939f7b0bb87d6@haskell.org> Message-ID: <060.1c403bc738f90f3576e92eb50d9ad945@haskell.org> #12150: Compile time performance degradation on code that uses undefined/error with CallStacks -------------------------------------+------------------------------------- Reporter: thomie | Owner: Type: bug | Status: new Priority: high | Milestone: 8.0.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: #10844 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by gridaphobe): Yes, sorry! I dusted off the old no-inline patch a couple weeks ago, made a few tweaks, and noticed better results, but I haven't had a chance to clean it up for review yet. I'll try to get it into Phab this week. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 19 13:26:57 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 19 Jul 2016 13:26:57 -0000 Subject: [GHC] #12274: GHC panic: simplifier ticks exhausted In-Reply-To: <045.2b6954bdf1af859f773f3b4e8826a3f4@haskell.org> References: <045.2b6954bdf1af859f773f3b4e8826a3f4@haskell.org> Message-ID: <060.0e87357d5e6655ca4afb9f60584e3f30@haskell.org> #12274: GHC panic: simplifier ticks exhausted -------------------------------------+------------------------------------- Reporter: mrkkrp | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 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 thomie): * failure: Compile-time crash => Compile-time performance bug Comment: Some notes: * There are a lot of `INLINE` pragmas in `Text.Mustache.Parser`, maybe too many? For example, removing the `INLINE` on `symbol` fixes the panic. * A `simpl-tick-factor` of `110` fixes the panic, so the simplifier is going only very slightly over the limit. This is probably nothing to worry about. * The regression in compile time is the real problem. Fixing it will fix the panic as well. I reduced it to the following testcase: https://github.com/thomie/megaslow (no external dependencies). Instructions: {{{ $ ghc -O Char.hs $ ghc -O -c -Rghc-timing Test.hs }}} ||= GHC =||= Bytes allocated for `Test.hs` =|| || 7.8.4 || 117MB || || 7.10.3 || 750MB || || HEAD (ffe4660510a7ba4adce846f316db455ccd91142a) || 724MB || -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 19 13:59:01 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 19 Jul 2016 13:59:01 -0000 Subject: [GHC] #12365: Update documentation for partial type signatures In-Reply-To: <047.cbfa181c69d689f1b05c74fd008c67ae@haskell.org> References: <047.cbfa181c69d689f1b05c74fd008c67ae@haskell.org> Message-ID: <062.14e1cb6a6d851094251abfe8c8faa896@haskell.org> #12365: Update documentation for partial type signatures -------------------------------------+------------------------------------- Reporter: goldfire | Owner: 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: | -------------------------------------+------------------------------------- Changes (by thomie): * cc: thomasw (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 19 14:12:45 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 19 Jul 2016 14:12:45 -0000 Subject: [GHC] #12274: GHC panic: simplifier ticks exhausted In-Reply-To: <045.2b6954bdf1af859f773f3b4e8826a3f4@haskell.org> References: <045.2b6954bdf1af859f773f3b4e8826a3f4@haskell.org> Message-ID: <060.8476afe617df33462ace681358911e54@haskell.org> #12274: GHC panic: simplifier ticks exhausted -------------------------------------+------------------------------------- Reporter: mrkkrp | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 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 simonpj): Interesting. Thanks for reducing the test case. No time to look at it now, but can you characterise what is happening more. E.g. what happens with `-dshow-passes`? Does the program get really big at some point? What's the difference between 7.8 and 7.10. Is it non-linear somehow? etc. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 19 14:23:14 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 19 Jul 2016 14:23:14 -0000 Subject: [GHC] #12409: Unboxed tuples have no type representations In-Reply-To: <046.32a785a6183ec0ab7732a4ef59760aa4@haskell.org> References: <046.32a785a6183ec0ab7732a4ef59760aa4@haskell.org> Message-ID: <061.72cb15e8becb531bea96eacbf9cc609c@haskell.org> #12409: Unboxed tuples have no type representations -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: bug | Status: new Priority: normal | Milestone: 8.0.2 Component: Compiler | Version: 8.0.1 Resolution: | Keywords: typeable Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: 11736 | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): Yes -- for now, a more polite error would suffice I think. Anyway, it's unrelated to the other stuff about knownTyCons etc. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 19 14:31:33 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 19 Jul 2016 14:31:33 -0000 Subject: [GHC] #12386: Infinite loop when showing type family error In-Reply-To: <047.61d384525fef8c0da8d7346e45b629d6@haskell.org> References: <047.61d384525fef8c0da8d7346e45b629d6@haskell.org> Message-ID: <062.a8089cce37c3405efb1e28bb774b1470@haskell.org> #12386: Infinite loop when showing type family error -------------------------------------+------------------------------------- Reporter: elliottt | Owner: simonpj 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 simonpj): * owner: => simonpj Comment: I'm on this. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 19 14:32:33 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 19 Jul 2016 14:32:33 -0000 Subject: [GHC] #12365: Update documentation for partial type signatures In-Reply-To: <047.cbfa181c69d689f1b05c74fd008c67ae@haskell.org> References: <047.cbfa181c69d689f1b05c74fd008c67ae@haskell.org> Message-ID: <062.95ed0ba7fc08d4733ad8d0cbeeba3ec0@haskell.org> #12365: Update documentation for partial type signatures -------------------------------------+------------------------------------- Reporter: goldfire | Owner: thomasw 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: | -------------------------------------+------------------------------------- Changes (by thomasw): * owner: => thomasw -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 19 15:11:38 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 19 Jul 2016 15:11:38 -0000 Subject: [GHC] #12365: Update documentation for partial type signatures In-Reply-To: <047.cbfa181c69d689f1b05c74fd008c67ae@haskell.org> References: <047.cbfa181c69d689f1b05c74fd008c67ae@haskell.org> Message-ID: <062.91d16b0126826b8d1be75cb56c62caa7@haskell.org> #12365: Update documentation for partial type signatures -------------------------------------+------------------------------------- Reporter: goldfire | Owner: thomasw 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): Phab:D2413 Wiki Page: | -------------------------------------+------------------------------------- Changes (by thomasw): * differential: => Phab:D2413 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 19 15:51:21 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 19 Jul 2016 15:51:21 -0000 Subject: [GHC] #12357: Increasing maximum constraint tuple size significantly blows up compiler allocations In-Reply-To: <046.dd0f12e974ac3c5c9febd70397bf4138@haskell.org> References: <046.dd0f12e974ac3c5c9febd70397bf4138@haskell.org> Message-ID: <061.21c00a9054b19c45e03f6e5ea641c28c@haskell.org> #12357: Increasing maximum constraint tuple size significantly blows up compiler allocations -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.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:D2400 Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): Replying to [comment:23 simonpj]: > Why/how does the `TcTypeable` impl rely on them being there??? There jolly well ought to be a comment to say so. > It looks like my memory failed me here: `TcTypeable` relies on `primTyCons`, not `allKnownKeyNames`, to create the representations for primitive types. That being said, excluding tuples from the name cache nevertheless poses a problem for `Typeable`: Currently type representations for tuples are known key. If we exclude tuple type representations from the known key list then they will be loaded from `GHC/Tuple.hi` with the wrong unique. There are two ways of dealing with this that are immediately obvious but not terribly appealing, * Add a special encoding to the symbol table format for type rep names. However, it seems odd to add special encodings in the interface file format for such a narrow case * Add support to the `isBuiltInOcc_maybe` parser for identifying `$tc` names. > All I see is > > * `knownKeyNames` used in building `knownKeyNamesMap` in `BinIface`. Waste of time having tuples in there because they are treated specially by `BinIface`. > > * Initialising the name cache in `HscMain`. > > And that's really it. Yes, I agree. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 19 15:57:06 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 19 Jul 2016 15:57:06 -0000 Subject: [GHC] #8171: Extending ExtendedDefaultRules In-Reply-To: <045.d77bd9544286ea508e1fa1aea2399f0c@haskell.org> References: <045.d77bd9544286ea508e1fa1aea2399f0c@haskell.org> Message-ID: <060.6aceb3d9baf3dad57a76fd7a59391977@haskell.org> #8171: Extending ExtendedDefaultRules -------------------------------------+------------------------------------- Reporter: ekmett | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.6.3 Resolution: | Keywords: | ExtendedDefaultRules Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #2641 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by crockeea): * cc: ecrockett0@… (added) Comment: Also see #12271. My primary concern there is GHC rather than GHCi. My main point there is: users should be able to specify defaults for user-defined /non-Prelude constraints; defaulting should not be a magical property baked into specific Prelude typeclasses. It sounds like the solution proposed here would require -XEDR, whereas my proposed solution just modifies the existing `default` tuple, similar to what Edward suggested at the end of [https://ghc.haskell.org/trac/ghc/ticket/8171#comment:4 comment 4]. I think removing rule 3 from the EDRs would effectively remove the "magic" that I talk about in that ticket. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 19 15:58:46 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 19 Jul 2016 15:58:46 -0000 Subject: [GHC] #12357: Increasing maximum constraint tuple size significantly blows up compiler allocations In-Reply-To: <046.dd0f12e974ac3c5c9febd70397bf4138@haskell.org> References: <046.dd0f12e974ac3c5c9febd70397bf4138@haskell.org> Message-ID: <061.25c1a9e4ec8d3fd76b5acc279c2dd911@haskell.org> #12357: Increasing maximum constraint tuple size significantly blows up compiler allocations -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.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:D2400 Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): > If we exclude tuple type representations from the known key list then they will be loaded from GHC/Tuple.hi with the wrong unique I don't understand. Isn't that what `-- Note [Symbol table representation of names]` is all about? What gets loaded with the wrong key? > Add a special encoding to the symbol table format for type rep names. However, it seems odd to add special encodings in the interface file format for such a narrow case Not really. We already have {{{ -- A tuple name: -- x is the tuple sort (00b ==> boxed, 01b ==> unboxed, 10b ==> constraint) -- y is the thing (00b ==> tycon, 01b ==> datacon, 10b ==> datacon worker) -- z is the arity }}} Data con workers seems similarly specialised. It's just an encoding for a large family. Maybe 11b for rep-name? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 19 15:58:57 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 19 Jul 2016 15:58:57 -0000 Subject: [GHC] #12271: Remove magic from type defaulting In-Reply-To: <047.ae1779973d06ce4533efe23eea81797f@haskell.org> References: <047.ae1779973d06ce4533efe23eea81797f@haskell.org> Message-ID: <062.e8d7f7b566c5719b57bcb7801295eaa4@haskell.org> #12271: Remove magic from type defaulting -------------------------------------+------------------------------------- Reporter: crockeea | Owner: Type: feature request | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: duplicate | Keywords: | ExtendedDefaultRules Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: 8171 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by crockeea): * status: new => closed * resolution: => duplicate * related: => 8171 Comment: I believe that ticket covers this case. I made added a comment there; closing this as duplicate. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 19 16:01:48 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 19 Jul 2016 16:01:48 -0000 Subject: [GHC] #12357: Increasing maximum constraint tuple size significantly blows up compiler allocations In-Reply-To: <046.dd0f12e974ac3c5c9febd70397bf4138@haskell.org> References: <046.dd0f12e974ac3c5c9febd70397bf4138@haskell.org> Message-ID: <061.ba84cfbdb2cbfba9424200d05163e45f@haskell.org> #12357: Increasing maximum constraint tuple size significantly blows up compiler allocations -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.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:D2400 Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): Replying to [comment:27 simonpj]: > > If we exclude tuple type representations from the known key list then they will be loaded from GHC/Tuple.hi with the wrong unique > > I don't understand. Isn't that what `-- Note [Symbol table representation of names]` > is all about? What gets loaded with the wrong key? > The `TypeRepName` (e.g. `$tc(,,)`). > > Add a special encoding to the symbol table format for type rep names. However, it seems odd to add special encodings in the interface file format for such a narrow case > > Not really. We already have > {{{ > -- A tuple name: > -- x is the tuple sort (00b ==> boxed, 01b ==> unboxed, 10b ==> constraint) > -- y is the thing (00b ==> tycon, 01b ==> datacon, 10b ==> datacon worker) > -- z is the arity > }}} > Data con workers seems similarly specialised. It's just an encoding for a large family. Maybe 11b for rep-name? Fair enough. Alright; I'll move ahead with this option then. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 19 16:19:07 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 19 Jul 2016 16:19:07 -0000 Subject: [GHC] #12357: Increasing maximum constraint tuple size significantly blows up compiler allocations In-Reply-To: <046.dd0f12e974ac3c5c9febd70397bf4138@haskell.org> References: <046.dd0f12e974ac3c5c9febd70397bf4138@haskell.org> Message-ID: <061.fff6b5ed981fb70dad721ba133c3f45f@haskell.org> #12357: Increasing maximum constraint tuple size significantly blows up compiler allocations -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.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:D2400 Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): > > Data con workers seems similarly specialised. It's just an encoding for a large family. Maybe 11b for rep-name? > Fair enough. Alright; I'll move ahead with this option then. On second thought, this is actually not entirely trivial; to see why, consider what happens when you are writing out the interface file of `GHC.Tuple`. Under the proposal, you would need to somehow recognize type representations (which are plain value-level bindings) which belong to a tuple type and encode them with the special symbol table encoding. Indeed we already do this for encoding `TyCon` names and it's not hard: just look for `TyCon`s with `algTcRhs = TupleTyCon {}` (as is done by `tyConTuple_maybe`). However, distinguishing a value level binding as a tuple's type rep is not as easy. I can think of two options neither being terribly nice, 1. Build a `Map TypeRepName TupleSort` and check it for every symbol that we write to the symbol table (yuck) 2. Add a constructor to `IdDetails` to encode the fact that the binding is the typerep of a tuple -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 19 16:38:35 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 19 Jul 2016 16:38:35 -0000 Subject: [GHC] #12357: Increasing maximum constraint tuple size significantly blows up compiler allocations In-Reply-To: <046.dd0f12e974ac3c5c9febd70397bf4138@haskell.org> References: <046.dd0f12e974ac3c5c9febd70397bf4138@haskell.org> Message-ID: <061.b94bca5269530b1f614c5f06e370c29e@haskell.org> #12357: Increasing maximum constraint tuple size significantly blows up compiler allocations -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.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:D2400 Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): I've moved ahead with option 2 of comment:29 for now. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 19 16:59:26 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 19 Jul 2016 16:59:26 -0000 Subject: [GHC] #12410: Somehow detect splicing in ghci Message-ID: <051.68fec2e99046d2d08b438c5a4bbecc1c@haskell.org> #12410: Somehow detect splicing in ghci -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: 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 no TH expert but currently it seems you need a hack (adding `data X ;` or `pure []`) to do the following {{{ ghci> $(reify ''() >>= runIO.print >> return []) :210:3: error: • Couldn't match type ‘[t0]’ with ‘Exp’ Expected type: ExpQ Actual type: Q [t0] • In the expression: reify ''() >>= runIO . print >> return [] In the untyped splice: $(reify ''() >>= runIO . print >> return []) }}} {{{#!hs >>> data X; $(reify ''() >>= runIO.print >> return []) TyConI (DataD [] GHC.Tuple.() [] Nothing [NormalC GHC.Tuple.() []] []) >>> pure []; $(reify ''() >>= runIO.print >> return []) TyConI (DataD [] GHC.Tuple.() [] Nothing [NormalC GHC.Tuple.() []] []) }}} Same with [https://hackage.haskell.org/package/lens-4.14/docs/Control- Lens-TH.html#v:makeLenses makeLenses] (discussed [https://artyom.me/lens- over-tea-6 here], [https://github.com/ekmett/lens/issues/461 there]): {{{ >>> data A = B { _int :: Int } >>> makeLenses ''A :209:1: error: • No instance for (Show DecsQ) arising from a use of ‘print’ • In a stmt of an interactive GHCi command: print it }}} the following two work {{{#!hs >>> data A = B { _int :: Int } >>> pure []; makeLenses ''A >>> view int (B 42) 42 }}} {{{#!hs >>> data A = B { _int :: Int }; makeLenses ''A >>> view int (B 42) 42 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 19 17:03:30 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 19 Jul 2016 17:03:30 -0000 Subject: [GHC] #12411: GHC panic on TypeApplications + TemplateHaskell Message-ID: <051.e143c87e78ab86ca3c4b0272288715fe@haskell.org> #12411: GHC panic on TypeApplications + TemplateHaskell -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Keywords: | Operating System: Unknown/Multiple TypeApplications, TemplateHaskell | Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- This fails {{{ $ ghci -XTemplateHaskell -ignore-dot-ghci GHCi, version 8.0.1: http://www.haskell.org/ghc/ :? for help Prelude> import Control.Lens Prelude Control.Lens> data A = B { _int :: Int } Prelude Control.Lens> pure @Q []; makeLenses ''A ghc: panic! (the 'impossible' happened) (GHC version 8.0.1 for x86_64-unknown-linux): tcMonoExpr _ Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug Prelude Control.Lens> }}} sorry, don't have time for more detail -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 19 17:10:47 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 19 Jul 2016 17:10:47 -0000 Subject: [GHC] #12410: Somehow detect splicing in ghci In-Reply-To: <051.68fec2e99046d2d08b438c5a4bbecc1c@haskell.org> References: <051.68fec2e99046d2d08b438c5a4bbecc1c@haskell.org> Message-ID: <066.c09492ce39c3cc05590a33cb93e07a9e@haskell.org> #12410: Somehow detect splicing in ghci -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: 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 Iceland_jack: @@ -25,1 +25,3 @@ - over-tea-6 here], [https://github.com/ekmett/lens/issues/461 there]): + over-tea-6 here], [https://github.com/ekmett/lens/issues/461 there], + [https://www.reddit.com/r/haskelltil/comments/3ghacj/you_can_use_template_haskell_functions_like/ + hither]): New description: I'm no TH expert but currently it seems you need a hack (adding `data X ;` or `pure []`) to do the following {{{ ghci> $(reify ''() >>= runIO.print >> return []) :210:3: error: • Couldn't match type ‘[t0]’ with ‘Exp’ Expected type: ExpQ Actual type: Q [t0] • In the expression: reify ''() >>= runIO . print >> return [] In the untyped splice: $(reify ''() >>= runIO . print >> return []) }}} {{{#!hs >>> data X; $(reify ''() >>= runIO.print >> return []) TyConI (DataD [] GHC.Tuple.() [] Nothing [NormalC GHC.Tuple.() []] []) >>> pure []; $(reify ''() >>= runIO.print >> return []) TyConI (DataD [] GHC.Tuple.() [] Nothing [NormalC GHC.Tuple.() []] []) }}} Same with [https://hackage.haskell.org/package/lens-4.14/docs/Control- Lens-TH.html#v:makeLenses makeLenses] (discussed [https://artyom.me/lens- over-tea-6 here], [https://github.com/ekmett/lens/issues/461 there], [https://www.reddit.com/r/haskelltil/comments/3ghacj/you_can_use_template_haskell_functions_like/ hither]): {{{ >>> data A = B { _int :: Int } >>> makeLenses ''A :209:1: error: • No instance for (Show DecsQ) arising from a use of ‘print’ • In a stmt of an interactive GHCi command: print it }}} the following two work {{{#!hs >>> data A = B { _int :: Int } >>> pure []; makeLenses ''A >>> view int (B 42) 42 }}} {{{#!hs >>> data A = B { _int :: Int }; makeLenses ''A >>> view int (B 42) 42 }}} -- -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 19 17:34:16 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 19 Jul 2016 17:34:16 -0000 Subject: [GHC] #12410: Somehow detect splicing in ghci In-Reply-To: <051.68fec2e99046d2d08b438c5a4bbecc1c@haskell.org> References: <051.68fec2e99046d2d08b438c5a4bbecc1c@haskell.org> Message-ID: <066.685e59950c360d2ce7900f672f0a9ec3@haskell.org> #12410: Somehow detect splicing in ghci -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: 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 Blaisorblade): * cc: Blaisorblade (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 19 17:46:01 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 19 Jul 2016 17:46:01 -0000 Subject: [GHC] #12357: Increasing maximum constraint tuple size significantly blows up compiler allocations In-Reply-To: <046.dd0f12e974ac3c5c9febd70397bf4138@haskell.org> References: <046.dd0f12e974ac3c5c9febd70397bf4138@haskell.org> Message-ID: <061.a62c933031e88321850a0646e6e39d54@haskell.org> #12357: Increasing maximum constraint tuple size significantly blows up compiler allocations -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.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:D2400 Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): Unfortunately it looks like option 2 is somewhat of a dead-end as it would require that we make all of the type reps `WiredIn`, since we need to be able to look up the `Id` from the `Name` in order to inspect the `IdDetails`. This is all very yucky. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 19 18:51:18 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 19 Jul 2016 18:51:18 -0000 Subject: [GHC] #12274: GHC panic: simplifier ticks exhausted In-Reply-To: <045.2b6954bdf1af859f773f3b4e8826a3f4@haskell.org> References: <045.2b6954bdf1af859f773f3b4e8826a3f4@haskell.org> Message-ID: <060.03bb14da78694c8153a5ba6537079ca6@haskell.org> #12274: GHC panic: simplifier ticks exhausted -------------------------------------+------------------------------------- Reporter: mrkkrp | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 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 thomie): The problems start in the `Specialise` phase: {{{ # 7.8.4: # Result size of Simplifier = {terms: 62, types: 158, coercions: 1} # Result size of Specialise = {terms: 62, types: 158, coercions: 1} # # 7.10.3: # Result size of Simplifier = {terms: 66, types: 158, coercions: 1} # Result size of Specialise = {terms: 751, types: 2,319, coercions: 169} }}} * The output of `-ddump-spec` for `7.10` contains a list of `Local rules for imported ids`, but none for `7.8`. * The output of `-ddump-rule-firings` contains 326 rules for `7.10`, but only `20` for `7.8`. Some of the rule firings with `7.10`: {{{ Rule fired: Class op eof Rule fired: Class op fmap Rule fired: Class op fmap Rule fired: Class op $p1Stream Rule fired: Class op uncons Rule fired: Class op updatePos Rule fired: Class op updatePos Rule fired: Class op uncons Rule fired: Class op updatePos Rule fired: Class op updatePos Rule fired: Class op uncons Rule fired: Class op updatePos Rule fired: Class op updatePos Rule fired: Class op uncons Rule fired: Class op updatePos Rule fired: Class op updatePos Rule fired: SPEC/Test $fApplicativeParsecT @ Dec @ [Char] @ Identity Rule fired: SPEC/Test $fAlternativeParsecT @ Dec @ [Char] @ Identity Rule fired: Class op pure Rule fired: Class op pure ... ... ... }}} Here is a simplified example: Test.hs: {{{#!hs module Test where import A xs = mymap (+1) [1,2,3] }}} A.hs: {{{#!hs module A where mymap :: Functor f => (a -> b) -> f a -> f b mymap = fmap }}} ghc-7.8.4: {{{ $ ghc-7.8.4 Test.hs -ddump-rule-firings -O -fforce-recomp [1 of 2] Compiling A ( A.hs, A.o ) [2 of 2] Compiling Test ( Test.hs, Test.o ) Rule fired: Class op + Rule fired: Class op fmap Rule fired: map Rule fired: mapList }}} ghc-7.10.3: {{{ $ ghc-7.10.3 Test.hs -ddump-rule-firings -O -fforce-recomp [1 of 2] Compiling A ( A.hs, A.o ) [2 of 2] Compiling Test ( Test.hs, Test.o ) Rule fired: Class op + Rule fired: Class op fmap Rule fired: Class op fmap Rule fired: Class op fmap Rule fired: map Rule fired: mapList }}} Why does the `Class op fmap` fire three times with 7.10.3? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 19 19:21:22 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 19 Jul 2016 19:21:22 -0000 Subject: [GHC] #12357: Increasing maximum constraint tuple size significantly blows up compiler allocations In-Reply-To: <046.dd0f12e974ac3c5c9febd70397bf4138@haskell.org> References: <046.dd0f12e974ac3c5c9febd70397bf4138@haskell.org> Message-ID: <061.cdbac17329699e170e9deaf170e0da99@haskell.org> #12357: Increasing maximum constraint tuple size significantly blows up compiler allocations -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.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:D2400 Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): And as it turns out wiring in the tuple type constructors representations has further knock-on consequence, requiring that we yet again wire-in `Data.Typeable.Internal.Module` and `Data.Typeable.Internal.TrName`. Recall that we unwired these around six months ago (ticket:11120#comment:28) due to breakage in GHCJS due to the varying width of `Fingerprint` on 32- and 64-bit platforms. For what it's worth, this varying width would be fixed if #11953 were implemented. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 19 19:30:30 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 19 Jul 2016 19:30:30 -0000 Subject: [GHC] #12410: Somehow detect splicing in ghci In-Reply-To: <051.68fec2e99046d2d08b438c5a4bbecc1c@haskell.org> References: <051.68fec2e99046d2d08b438c5a4bbecc1c@haskell.org> Message-ID: <066.494dfc8a1b91487460bd0a9029df862f@haskell.org> #12410: Somehow detect splicing in ghci -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: 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: | -------------------------------------+------------------------------------- Changes (by goldfire): * component: Compiler => Template Haskell Comment: GHCi sees splices as ''expression'' splices. You want a ''declaration'' splice. The truth is that either one is reasonable. But perhaps GHCi can detect what you mean by the types and Do The Right Thing. Just like it already does to detect when you want an `IO` action. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 19 19:55:12 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 19 Jul 2016 19:55:12 -0000 Subject: [GHC] #12357: Increasing maximum constraint tuple size significantly blows up compiler allocations In-Reply-To: <046.dd0f12e974ac3c5c9febd70397bf4138@haskell.org> References: <046.dd0f12e974ac3c5c9febd70397bf4138@haskell.org> Message-ID: <061.cb245a42ed4b035ede582e603e6fbc44@haskell.org> #12357: Increasing maximum constraint tuple size significantly blows up compiler allocations -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.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:D2400 Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): OK, you are right. Let's NOT wire-in the rep-names. That would be bad. I recant on comment:27. Lesser evil is to add the rep-names of boxed tuples (but still not the tuple tycons or data cons) to the known-key names, and otherwise not treat them specially. Unboxed and constratint tuples (and uncoming unboxed sums) remain un- representable, but that's a problem for another day. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 19 21:21:13 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 19 Jul 2016 21:21:13 -0000 Subject: [GHC] #12357: Increasing maximum constraint tuple size significantly blows up compiler allocations In-Reply-To: <046.dd0f12e974ac3c5c9febd70397bf4138@haskell.org> References: <046.dd0f12e974ac3c5c9febd70397bf4138@haskell.org> Message-ID: <061.503ffbc322404574902c63f333b00d2b@haskell.org> #12357: Increasing maximum constraint tuple size significantly blows up compiler allocations -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: bug | Status: patch Priority: normal | Milestone: Component: Compiler | Version: 7.10.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:D2400, Wiki Page: | Phab:D2414 -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => patch * differential: Phab:D2400 => Phab:D2400, Phab:D2414 Comment: Here's a first cut at a fix. Currently have a validation running and I likely need to do another pass over the comments when I'm less tired. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 19 22:19:27 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 19 Jul 2016 22:19:27 -0000 Subject: [GHC] #12412: SIMD things introduce a metric ton of known key things Message-ID: <046.cd884b3e798e0694f3f465a42e24806f@haskell.org> #12412: SIMD things introduce a metric ton of known key things -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: bug | Status: new Priority: low | Milestone: Component: Compiler | Version: 8.0.1 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: -------------------------------------+------------------------------------- In #12357 we were looking at reducing the number of entries in the `knownKeyNames`. This has the potential to improve compiler performance since this set of things is always present in the original name cache, which is often referred to. #12357 reduced the number of elements in `knownKeyNames` from 2017 to 1834. Not a bad improvement. That being said, the SIMD operations introduce nearly four times that number. These include things like `readWord64OffAddrAsWord64X2#`, `indexInt16OffAddrAsInt16X16#`, and `remInt16X16#`. All in all these operations constitute nearly a third of the known key names. I'm not really sure what can be done about this, but I thought it should be noted. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 19 22:31:27 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 19 Jul 2016 22:31:27 -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.ed02cb059c446a2d74ee3189e1234fb2@haskell.org> #12412: SIMD things introduce a metric ton of known key things -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: bug | Status: new Priority: low | Milestone: 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 simonpj): As far as I know, nothing in #12357 suggested that the size of the `knownKeyNames` had the slightest impact on performance. I'm very un- bothered by the number of `knownKeyNames` until I see evidence that it has some impact. Why shoudl we care? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 19 22:46:57 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 19 Jul 2016 22:46:57 -0000 Subject: [GHC] #12274: GHC panic: simplifier ticks exhausted In-Reply-To: <045.2b6954bdf1af859f773f3b4e8826a3f4@haskell.org> References: <045.2b6954bdf1af859f773f3b4e8826a3f4@haskell.org> Message-ID: <060.949dd95dd2e94f3ffe5a349a817466e1@haskell.org> #12274: GHC panic: simplifier ticks exhausted -------------------------------------+------------------------------------- Reporter: mrkkrp | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 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 simonpj): GHC 7.10 makes specialised versions of imported overloaded functions, at least if it can see its inlining. In the example * `mymap` is overloaded, and is small, so its inlining is visible to module `Test` * `mymap` is called at type `Integer` in `Test` so GHC makes specialised copy, and adds a local RULE to rewrite `mymap Integer` to `$smymap`. * The `fmap` rule fires twice, once in the RHS of `$smymap` and once in its (small) unfolding. * But when GHC encounters the call to `mymap` is just inlines it anyway, before thinking about rules. That exposes another call to `fmap` so the rule fires again. Because `mymap` inlines, all the specalisation is in vain. How to avoid that? Maybe one round of simplification so that outright inlining precedes any attempt to specialise. Whether this is the original problem, I'm not sure. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 19 22:50:22 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 19 Jul 2016 22:50:22 -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.c0729c1ef0073ff2d5c30e70146fcc9d@haskell.org> #12412: SIMD things introduce a metric ton of known key things -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: bug | Status: new Priority: low | Milestone: 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 bgamari): > As far as I know, nothing in #12357 suggested that the size of the `knownKeyNames` had the slightest impact on performance. It's not clear that we should. I merely opened this ticket so I had someplace to write the answer when I find out whether this is something worth worrying about, otherwise I would have surely forgotten. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 20 00:41:47 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 20 Jul 2016 00:41:47 -0000 Subject: [GHC] #12410: Somehow detect splicing in ghci In-Reply-To: <051.68fec2e99046d2d08b438c5a4bbecc1c@haskell.org> References: <051.68fec2e99046d2d08b438c5a4bbecc1c@haskell.org> Message-ID: <066.03da84cbb755c7d2fdc111681714a180@haskell.org> #12410: Somehow detect splicing in ghci -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: 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 Iceland_jack): Replying to [comment:3 goldfire]: > But perhaps GHCi can detect what you mean by the types and Do The Right Thing. Just like it already does to detect when you want an `IO` action. Yes I had something like that in mind, detect if the type is `DecsQ` ---- Side note: {{{#!hs -- WORKS >>> pure @Q @[Dec] []; $(reify ''() >>= runIO.print >> return []) TyConI (DataD [] GHC.Tuple.() [] Nothing [NormalC GHC.Tuple.() []] []) }}} {{{#!hs -- WORKS >>> (pure [] :: DecsQ); $(reify ''() >>= runIO.print >> return []) TyConI (DataD [] GHC.Tuple.() [] Nothing [NormalC GHC.Tuple.() []] []) }}} {{{#!hs -- DOESN'T >>> pure [] :: DecsQ; $(reify ''() >>= runIO.print >> return []) :374:1: error: Invalid type signature: pure [] :: ... Should be of form :: }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 20 08:38:57 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 20 Jul 2016 08:38:57 -0000 Subject: [GHC] #11981: unknown symbol `__udivti3' when BuildFlavour = perf-llvm In-Reply-To: <044.ad3f32463aae7c699d4d4bd8ae6b6c27@haskell.org> References: <044.ad3f32463aae7c699d4d4bd8ae6b6c27@haskell.org> Message-ID: <059.abae477f8b0aaf0080c7eca894aa802b@haskell.org> #11981: unknown symbol `__udivti3' when BuildFlavour = perf-llvm -------------------------------------+------------------------------------- Reporter: erikd | Owner: Type: bug | Status: new Priority: normal | Milestone: 8.0.2 Component: Compiler | Version: 8.1 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 erikd): The function `__udivti3` seems to be a 128 bit `div` operation that is implemented in LLVM's "compiler-rt" library and in gcc "libgcc". Going to try and see if I can link libgcc. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 20 09:30:18 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 20 Jul 2016 09:30:18 -0000 Subject: [GHC] #12368: Demand Analyzer: Cunnig plan not adhered to with aborting fixpoint interation In-Reply-To: <046.2b784c018fc4a62b657688676ee901f3@haskell.org> References: <046.2b784c018fc4a62b657688676ee901f3@haskell.org> Message-ID: <061.8feeee9a0d4170b09e4a1c98ca16c2aa@haskell.org> #12368: Demand Analyzer: Cunnig plan not adhered to with aborting fixpoint interation -------------------------------------+------------------------------------- Reporter: nomeata | Owner: Type: bug | 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:D2392 Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): Sorry to be slow. I've looked at this and I don't agree with it at all! In the current code, if we hit the iteration limit we do this: {{{ loop' n env pairs | n >= 10 = (env, lazy_fv, orig_pairs) -- Safe output }}} So we return an un-decorated binding `orig_pairs` but (wrongly) an extended environment `env`. We should just return the un-extended environment! (If a variable isn't in the environment it's treated as having `topSig`.) Simple. Well, not totally simple. There is a nasty corner case, when we have nested recursive bindings: {{{ f x = ...let g y = ...y... in ... }}} Suppose that * on the first `f` iteration we find a fixpoint for `g` which we attach to it. * But on the second `f` iteration we fail to find a fixpoint for `g`. Then we should revert to `topSig`, not to the result of the first iteration. Conclusion: if the fixpoint limit is reached: * return an environment that simply does not mention the new binders * set all the binders to no-strictness-at-all Finally, the `loop` function in `dmdFix` would be much better if it took a `SigEnv` rather than an `AnalEnv`, wouldn't it? Just a simple refactoring; but the `ae_sigs` field is the only bit that varies. OK Joachim? Simon -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 20 09:53:27 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 20 Jul 2016 09:53:27 -0000 Subject: [GHC] #12368: Demand Analyzer: Cunnig plan not adhered to with aborting fixpoint interation In-Reply-To: <046.2b784c018fc4a62b657688676ee901f3@haskell.org> References: <046.2b784c018fc4a62b657688676ee901f3@haskell.org> Message-ID: <061.1984b5e83d4b562f07646384cbd8208b@haskell.org> #12368: Demand Analyzer: Cunnig plan not adhered to with aborting fixpoint interation -------------------------------------+------------------------------------- Reporter: nomeata | Owner: Type: bug | 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:D2392 Wiki Page: | -------------------------------------+------------------------------------- Comment (by nomeata): > So we return an un-decorated binding orig_pairs It is not necessarily un-decorated, but may have information from a previous pass of the Demand Analyzer. I was under the impression that we generally want to make sure that running the demand analyzer updates _all_ strictness signatures and demand information, and does not leave any around from a previous iteration. I am never fully confident that I can overlook all the assumptions in the code and the consequences, that’s why I am much more confident with simple invariants such as “all code has been processed and annotated by the demand analyzer at least once.” > We should just return the un-extended environment! (If a variable isn't in the environment it's treated as having topSig.) Simple. Is that safe? `topSig` (actually `nopSig`, since there is no top strictness signature) has an empty environment, so if the RHS of the definition makes use of a free variable, `nopSig` effectively has an absent demand on that. I guess this is the reason for the `lazy_fv` fuss. I think in some other discussion you wondered whether that is really required. By having the analysis set to `topSig` it definitely has to. > Conclusion: if the fixpoint limit is reached: > * return an environment that simply does not mention the new binders Agreed, if `lazy_fv` works as advertised. > * set all the binders to no-strictness-at-all What about demand and strictness signatures attached to binders somewhere nested in the RHS of one of the equation. Should we zap them as well? > Finally, the loop function in dmdFix would be much better if it took a SigEnv rather than an AnalEnv, wouldn't it? Or maybe even just a list of `StrSig`s, to make it clear that only the strictness signatures of the recursive binders vary. All in all I wonder if avoiding an extra iteration (after we already did 10) in the corner case is worth the extra complication of having to think about how to properly abort the analysis from in an invalid state. Simply jumping to a definitely sound state, and being able to guarantee that a pass of the demand analyzer processes all code appears to be simpler and more reliable to me. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 20 10:40:51 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 20 Jul 2016 10:40:51 -0000 Subject: [GHC] #12368: Demand Analyzer: Cunnig plan not adhered to with aborting fixpoint interation In-Reply-To: <046.2b784c018fc4a62b657688676ee901f3@haskell.org> References: <046.2b784c018fc4a62b657688676ee901f3@haskell.org> Message-ID: <061.ada075ff6b084f0e07fd62f1d0781306@haskell.org> #12368: Demand Analyzer: Cunnig plan not adhered to with aborting fixpoint interation -------------------------------------+------------------------------------- Reporter: nomeata | Owner: Type: bug | 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:D2392 Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): Yes that's the reason for the lazy_fv fuss! But that fuss is needed even when we do find a fixpoint. > What about demand and strictness signatures attached to binders somewhere nested in the RHS of one of the equation. Should we zap them as well? Ah, now that is an excellent point! Which should be carefully documented in a Note, eventually Yes ok. (I was not fussed about an extra iteration, just about clarity.) Let's do one more iteration. But we can do that simply with the original, unextended environment. I htink there is no need to do `addPessimisticSigs`. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 20 11:44:56 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 20 Jul 2016 11:44:56 -0000 Subject: [GHC] #12368: Demand Analyzer: Cunnig plan not adhered to with aborting fixpoint interation In-Reply-To: <046.2b784c018fc4a62b657688676ee901f3@haskell.org> References: <046.2b784c018fc4a62b657688676ee901f3@haskell.org> Message-ID: <061.4b207a4d5287bf98623133899f51d8bb@haskell.org> #12368: Demand Analyzer: Cunnig plan not adhered to with aborting fixpoint interation -------------------------------------+------------------------------------- Reporter: nomeata | Owner: Type: bug | 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:D2392 Wiki Page: | -------------------------------------+------------------------------------- Comment (by nomeata): > I think there is no need to do addPessimisticSigs. Ok, I will adjust the patch as requested, and add more ♫. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 20 12:11:22 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 20 Jul 2016 12:11:22 -0000 Subject: [GHC] #12371: Error message, room for improvement In-Reply-To: <051.4451bd27ef0d80311d9b31d3cc46b800@haskell.org> References: <051.4451bd27ef0d80311d9b31d3cc46b800@haskell.org> Message-ID: <066.a8af57c017a2bc59d988597e7a14dd2c@haskell.org> #12371: Error message, room for improvement -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: bug | Status: merge Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: | TypeApplications 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 simonpj): * status: new => merge Comment: Fixed in HEAD by {{{ commit e38c07bf5ceb8f50fa5110b70b3b83f0ce1358ba Author: Matthew Pickering Date: Thu Feb 25 15:51:46 2016 +0100 Improve accuracy of suggestion to use TypeApplications The suggestion only makes sense when we try to use an as pattern in an expression context. It is misleading in the case of a lazy pattern and view pattern. }}} May be worth merging? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 20 12:31:37 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 20 Jul 2016 12:31:37 -0000 Subject: [GHC] #12387: Template Haskell ignores class instance definitions with methods that don't belong to the class In-Reply-To: <050.eb69c313a059df9b62466d07df30fd0b@haskell.org> References: <050.eb69c313a059df9b62466d07df30fd0b@haskell.org> Message-ID: <065.1b8da4382c9ebb140e24329c0e510aca@haskell.org> #12387: Template Haskell ignores class instance definitions with methods that don't belong to the class -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Template Haskell | 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 simonpj): I made a little progress with this, which I'll record. The bug is here in `RnEnv.lookupSubBndrOcc`. Usually this function looks up an unqualified `RdrName` and uses the parent info in the `GlobalRdrEnv` to disambiguate; and to check that the specified name is indeed a method of the parent class. But here are in the `Exact` `RdrName` case: {{{ lookupSubBndrOcc warn_if_deprec the_parent doc rdr_name | Just n <- isExact_maybe rdr_name -- This happens in derived code = do { n <- lookupExactOcc n ; return (Right n) } }}} In the example `'compare` refers precisely to `GHC.Classes.compare`, so we get an `Exact` `RdrName`. But that `compare` may not even be in scope, and may not be in the `GlobalRdrEnv`. We are omitting a check for the correct parent; hence the lack of error message. What to do? Either * If it's not in scope it must presumably be imported and hence in the `TypeEnv`. So we could look for parent-hood that way. A bit of a pain. * Or we could postpone the check altogether to the typechecker. I like this plan better because it works uniformly for local and imported things. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 20 13:18:00 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 20 Jul 2016 13:18:00 -0000 Subject: [GHC] #12365: Update documentation for partial type signatures In-Reply-To: <047.cbfa181c69d689f1b05c74fd008c67ae@haskell.org> References: <047.cbfa181c69d689f1b05c74fd008c67ae@haskell.org> Message-ID: <062.0ad796ea1c421bfa1269db48e12f4c96@haskell.org> #12365: Update documentation for partial type signatures -------------------------------------+------------------------------------- Reporter: goldfire | Owner: thomasw 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): Phab:D2413 Wiki Page: | -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"627c767b8e5587de52086d8891d7f7aabf6fa49f/ghc" 627c767b/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="627c767b8e5587de52086d8891d7f7aabf6fa49f" Update docs for partial type signatures (#12365) * Update the sample error messages. The messages have been reworded and reformatted since GHC 7.10. * Mention `TypeApplications` in "Where can they occur?" * The name of a named wild card is no longer used in the name of a resulting type variable. Before: `_foo` => `w_foo`, now: `_foo` => `t` or `a`. Test Plan: generate the users guide Reviewers: goldfire, austin, bgamari Reviewed By: bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2413 GHC Trac Issues: #12365 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 20 13:18:00 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 20 Jul 2016 13:18:00 -0000 Subject: [GHC] #12402: Add fromLeft and fromRight to Data.Either In-Reply-To: <047.8d07fa3189133dd22d10c5fafc177522@haskell.org> References: <047.8d07fa3189133dd22d10c5fafc177522@haskell.org> Message-ID: <062.5b9caa027375efca5eae191d2f71b1d6@haskell.org> #12402: Add fromLeft and fromRight to Data.Either -------------------------------------+------------------------------------- Reporter: mettekou | Owner: Type: feature request | Status: closed Priority: normal | Milestone: Component: libraries/base | Version: 8.0.1 Resolution: fixed | Keywords: Data.Either, | fromLeft, fromRight Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2403 Wiki Page: | -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"a0f83a628cc6a00f948662f88e711c2a37bfda60/ghc" a0f83a62/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="a0f83a628cc6a00f948662f88e711c2a37bfda60" Data.Either: Add fromLeft and fromRight (#12402) Reviewers: austin, hvr, RyanGlScott, bgamari Reviewed By: RyanGlScott, bgamari Subscribers: RyanGlScott, thomie Differential Revision: https://phabricator.haskell.org/D2403 GHC Trac Issues: #12402 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 20 13:18:00 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 20 Jul 2016 13:18:00 -0000 Subject: [GHC] #12128: ghci cause panic on 8.0.1 In-Reply-To: <043.d0d8e98d01cc863c9b0e7ff6db6baf83@haskell.org> References: <043.d0d8e98d01cc863c9b0e7ff6db6baf83@haskell.org> Message-ID: <058.a9a682a81b3615568c69c721422d52c4@haskell.org> #12128: ghci cause panic on 8.0.1 -------------------------------------+------------------------------------- Reporter: zxtx | Owner: seraphime Type: bug | Status: patch Priority: high | Milestone: 8.0.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): Phab:D2374 Wiki Page: | -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"8de6e13f9ef784750e502955fcb38d4a7e179727/ghc" 8de6e13f/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="8de6e13f9ef784750e502955fcb38d4a7e179727" Fix bytecode generator panic This fixes #12128. The bug was introduced in 1c9fd3f1c5522372fcaf250c805b959e8090a62c. Test Plan: ./validate Reviewers: simonmar, austin, hvr, simonpj, bgamari Reviewed By: bgamari Subscribers: simonpj, thomie Differential Revision: https://phabricator.haskell.org/D2374 GHC Trac Issues: #12128 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 20 13:38:10 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 20 Jul 2016 13:38:10 -0000 Subject: [GHC] #12401: GHC panic! Template variable unbound in rewrite rule In-Reply-To: <048.bb29ad43ef422a099b000889adb7e842@haskell.org> References: <048.bb29ad43ef422a099b000889adb7e842@haskell.org> Message-ID: <063.b15eaa4d2b0949733a0ffe7d5b6674e9@haskell.org> #12401: GHC panic! Template variable unbound in rewrite rule -------------------------------------+------------------------------------- Reporter: vagarenko | Owner: Type: bug | Status: merge Priority: high | Milestone: 8.0.2 Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Windows | Architecture: x86_64 Type of failure: Compile-time | (amd64) crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * status: new => merge Comment: I think this is a dup of #12212. Certianly it works with HEAD. The fix for #12212 has been merged to the 8.0 branch, I think. I have not checked that it works with the 8.0 branch. I'll set status to 'merge' just to invite someone to test that. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 20 13:38:46 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 20 Jul 2016 13:38:46 -0000 Subject: [GHC] #12408: "ghc: panic! (the 'impossible' happened)" only when compiled with "-O" In-Reply-To: <046.d29ea653b6a5476c1904e0cd28bb26ab@haskell.org> References: <046.d29ea653b6a5476c1904e0cd28bb26ab@haskell.org> Message-ID: <061.07eb29c6375d9c55a88bcd96cf44f211@haskell.org> #12408: "ghc: panic! (the 'impossible' happened)" only when compiled with "-O" -------------------------------------+------------------------------------- Reporter: clinton | Owner: Type: bug | Status: merge Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 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): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * status: new => merge Comment: I think this is a dup of #12212. Certianly it works with HEAD; I checked. The fix for #12212 has been merged to the 8.0 branch, I think. I have not checked that it works with the 8.0 branch. I'll set status to 'merge' just to invite someone to test that. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 20 15:16:18 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 20 Jul 2016 15:16:18 -0000 Subject: [GHC] #11357: Regression when deriving Generic1 on poly-kinded data family In-Reply-To: <050.901cd59cca6d2d30c1ece6815b80ca65@haskell.org> References: <050.901cd59cca6d2d30c1ece6815b80ca65@haskell.org> Message-ID: <065.3bab6a542d10f48ee239dacfb1e0bd89@haskell.org> #11357: Regression when deriving Generic1 on poly-kinded data family -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: bug | Status: closed Priority: highest | Milestone: 8.0.1 Component: Compiler | Version: 7.11 (CodeGen) | Keywords: Generics, Resolution: fixed | TypeInType, TypeFamilies Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: GHC rejects | Test Case: valid program | deriving/should_compile/T11357 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"9513fe6bdeafd35ca1a04e17b5f94732516766aa/ghc" 9513fe6/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="9513fe6bdeafd35ca1a04e17b5f94732516766aa" Clean up interaction between name cache and built-in syntax This cleans up various aspects of the handling of built-in syntax in the original name cache (hopefully resulting in a nice reduction in compiler allocations), * Remove tuple types from original name cache: There is really no reason for these to be in the name cache since we already handle them specially in interface files to ensure that we can resolve them directly to Names, avoiding extraneous name cache lookups. * Sadly it's not possible to remove all traces of tuples from the name cache, however. Namely we need to keep the tuple type representations in since otherwise they would need to be wired-in * Remove the special cases for (:), [], and (##) in isBuiltInOcc_maybe and rename it to isTupleOcc_maybe * Split lookupOrigNameCache into two variants, * lookupOrigNameCache': Merely looks up an OccName in the original name cache, making no attempt to resolve tuples * lookupOrigNameCache: Like the above but handles tuples as well. This is given the un-primed name since it does the "obvious" thing from the perspective of an API user, who knows nothing of our special treatment of tuples. Arriving at this design took a significant amount of iteration. The trail of debris leading here can be found in #11357. Thanks to ezyang and Simon for all of their help in coming to this solution. Test Plan: Validate Reviewers: goldfire, simonpj, austin Reviewed By: simonpj Subscribers: thomie, ezyang Differential Revision: https://phabricator.haskell.org/D2414 GHC Trac Issues: #11357 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 20 15:16:18 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 20 Jul 2016 15:16:18 -0000 Subject: [GHC] #12367: Commit adding instances to GHC.Generics regression compiler performance In-Reply-To: <046.87a5f8a842934b4554eedf79fb6bebbc@haskell.org> References: <046.87a5f8a842934b4554eedf79fb6bebbc@haskell.org> Message-ID: <061.f1fcbc3f41d6e588b8c2e55f078a7853@haskell.org> #12367: Commit adding instances to GHC.Generics regression compiler performance -------------------------------------+------------------------------------- Reporter: bgamari | Owner: bgamari Type: bug | Status: patch Priority: normal | Milestone: 8.0.2 Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Generics 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:D2411 Wiki Page: | -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"ed4809813fa51524ae73a4475afe33018a67f87d/ghc" ed480981/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="ed4809813fa51524ae73a4475afe33018a67f87d" InstEnv: Ensure that instance visibility check is lazy Previously instIsVisible had completely broken the laziness of lookupInstEnv' since it would examine is_dfun_name to check the name of the defining module (to know whether it is an interactive module). This resulted in the visibility check drawing in an interface file unnecessarily. This contributed to the unnecessary regression in compiler allocations reported in #12367. Test Plan: Validate, check nofib changes Reviewers: simonpj, ezyang, austin Reviewed By: ezyang Subscribers: thomie, ezyang Differential Revision: https://phabricator.haskell.org/D2411 GHC Trac Issues: #12367 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 20 15:28:47 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 20 Jul 2016 15:28:47 -0000 Subject: [GHC] #12381: Type family not reduced In-Reply-To: <046.0dea1b11f4af8f3cac37c083d6847cd7@haskell.org> References: <046.0dea1b11f4af8f3cac37c083d6847cd7@haskell.org> Message-ID: <061.dc714279cadb5a13ec358eb5d757f3f6@haskell.org> #12381: Type family not reduced -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: bug | Status: merge Priority: normal | Milestone: 8.0.2 Component: Compiler (Type | Version: 8.0.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: | -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"a4f2b76661fa2056172b27b9883df1f488b7a0dc/ghc" a4f2b76/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="a4f2b76661fa2056172b27b9883df1f488b7a0dc" testsuite: Add regression test for #12381 Test Plan: Validate Reviewers: austin Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2408 GHC Trac Issues: #12381, #11348 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 20 15:28:47 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 20 Jul 2016 15:28:47 -0000 Subject: [GHC] #12082: Typeable on RealWorld fails In-Reply-To: <046.e4ee4338a41502e1434038b393cfe130@haskell.org> References: <046.e4ee4338a41502e1434038b393cfe130@haskell.org> Message-ID: <061.686e77dbbd2cb407dfb26db996287fc9@haskell.org> #12082: Typeable on RealWorld fails -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: bug | Status: closed Priority: high | Milestone: 8.0.2 Component: Compiler | Version: 8.0.1 Resolution: fixed | Keywords: Typeable Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | typecheck/should_run/TypeRep Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2240, Wiki Page: | Phab:D2239 -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"93acc02f7db7eb86967b4ec586359f408d62f75d/ghc" 93acc02f/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="93acc02f7db7eb86967b4ec586359f408d62f75d" Add another testcase for #12082 Test Plan: Validate, should pass. Reviewers: austin Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2399 GHC Trac Issues: #12082 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 20 15:28:47 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 20 Jul 2016 15:28:47 -0000 Subject: [GHC] #11348: Local open type families instances ignored during type checking In-Reply-To: <048.419b44d406ca8091f032a727fdd29058@haskell.org> References: <048.419b44d406ca8091f032a727fdd29058@haskell.org> Message-ID: <063.21c63417664fa543f856d416bf920cac@haskell.org> #11348: Local open type families instances ignored during type checking -------------------------------------+------------------------------------- Reporter: alexvieth | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 8.0.1-rc1 Resolution: fixed | Keywords: TypeFamilies Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: GHC rejects | Test Case: valid program | typecheck/should_compile/T11348 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D1762 Wiki Page: | -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"a4f2b76661fa2056172b27b9883df1f488b7a0dc/ghc" a4f2b76/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="a4f2b76661fa2056172b27b9883df1f488b7a0dc" testsuite: Add regression test for #12381 Test Plan: Validate Reviewers: austin Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2408 GHC Trac Issues: #12381, #11348 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 20 15:32:51 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 20 Jul 2016 15:32:51 -0000 Subject: [GHC] #12062: Parallel make with -j0 and hs-boot leads to floating point exception In-Reply-To: <045.f05741a711c24d381cb39c4a23db2a0e@haskell.org> References: <045.f05741a711c24d381cb39c4a23db2a0e@haskell.org> Message-ID: <060.f3ca2062b57d4384bc5eaf0a18f81e92@haskell.org> #12062: Parallel make with -j0 and hs-boot leads to floating point exception -------------------------------------+------------------------------------- Reporter: ezyang | Owner: petercommand Type: bug | Status: new Priority: low | Milestone: Component: Runtime System | Version: 8.0.1-rc2 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 petercommand): * owner: => petercommand -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 20 15:35:34 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 20 Jul 2016 15:35:34 -0000 Subject: [GHC] #11493: Merge compact normal forms In-Reply-To: <046.817f1145363bc4a821bde6cbb76b8fef@haskell.org> References: <046.817f1145363bc4a821bde6cbb76b8fef@haskell.org> Message-ID: <061.371783fa1eca8be101e82a15d89612e1@haskell.org> #11493: Merge compact normal forms -------------------------------------+------------------------------------- Reporter: bgamari | Owner: ezyang Type: task | Status: new Priority: normal | Milestone: 8.2.1 Component: | Version: 7.10.3 libraries/compact | 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 Marlow ): In [changeset:"cf989ffe490c146be4ed0fd7e0c00d3ff8fe1453/ghc" cf989ff/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="cf989ffe490c146be4ed0fd7e0c00d3ff8fe1453" Compact Regions This brings in initial support for compact regions, as described in the ICFP 2015 paper "Efficient Communication and Collection with Compact Normal Forms" (Edward Z. Yang et.al.) and implemented by Giovanni Campagna. Some things may change before the 8.2 release, but I (Simon M.) wanted to get the main patch committed so that we can iterate. What documentation there is is in the Data.Compact module in the new compact package. We'll need to extend and polish the documentation before the release. Test Plan: validate (new test cases included) Reviewers: ezyang, simonmar, hvr, bgamari, austin Subscribers: vikraman, Yuras, RyanGlScott, qnikst, mboes, facundominguez, rrnewton, thomie, erikd Differential Revision: https://phabricator.haskell.org/D1264 GHC Trac Issues: #11493 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 20 15:38:25 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 20 Jul 2016 15:38:25 -0000 Subject: [GHC] #12367: Commit adding instances to GHC.Generics regression compiler performance In-Reply-To: <046.87a5f8a842934b4554eedf79fb6bebbc@haskell.org> References: <046.87a5f8a842934b4554eedf79fb6bebbc@haskell.org> Message-ID: <061.d3ab64f02ea64ea113e13654d495ff90@haskell.org> #12367: Commit adding instances to GHC.Generics regression compiler performance -------------------------------------+------------------------------------- Reporter: bgamari | Owner: bgamari Type: bug | Status: patch Priority: normal | Milestone: 8.0.2 Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Generics 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:D2411 Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): The commit in comment:20 should hopefully make a significant dent in allocations. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 20 15:38:57 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 20 Jul 2016 15:38:57 -0000 Subject: [GHC] #12402: Add fromLeft and fromRight to Data.Either In-Reply-To: <047.8d07fa3189133dd22d10c5fafc177522@haskell.org> References: <047.8d07fa3189133dd22d10c5fafc177522@haskell.org> Message-ID: <062.c6bda0d26c49b087441bed0ee3cccaa1@haskell.org> #12402: Add fromLeft and fromRight to Data.Either -------------------------------------+------------------------------------- Reporter: mettekou | Owner: Type: feature request | Status: closed Priority: normal | Milestone: 8.2.1 Component: libraries/base | Version: 8.0.1 Resolution: fixed | Keywords: Data.Either, | fromLeft, fromRight Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2403 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * milestone: => 8.2.1 Comment: Thanks mettekou! -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 20 15:40:12 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 20 Jul 2016 15:40:12 -0000 Subject: [GHC] #11094: Cost-center heap profiler should be able to emit samples to eventlog In-Reply-To: <046.5020b7d3a1ba23f2949a42c6789e9133@haskell.org> References: <046.5020b7d3a1ba23f2949a42c6789e9133@haskell.org> Message-ID: <061.eb60409641813391f1000b725d6a245f@haskell.org> #11094: Cost-center heap profiler should be able to emit samples to eventlog -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: feature request | Status: closed Priority: normal | Milestone: 8.2.1 Component: Profiling | Version: 7.10.2 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Other | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D1722 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 Wed Jul 20 15:41:00 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 20 Jul 2016 15:41:00 -0000 Subject: [GHC] #12128: ghci cause panic on 8.0.1 In-Reply-To: <043.d0d8e98d01cc863c9b0e7ff6db6baf83@haskell.org> References: <043.d0d8e98d01cc863c9b0e7ff6db6baf83@haskell.org> Message-ID: <058.26c68a2a97965d1b3d9be48fab93ecd7@haskell.org> #12128: ghci cause panic on 8.0.1 -------------------------------------+------------------------------------- Reporter: zxtx | Owner: seraphime Type: bug | Status: merge Priority: high | Milestone: 8.0.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): Phab:D2374 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: patch => merge -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 20 15:41:18 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 20 Jul 2016 15:41:18 -0000 Subject: [GHC] #12365: Update documentation for partial type signatures In-Reply-To: <047.cbfa181c69d689f1b05c74fd008c67ae@haskell.org> References: <047.cbfa181c69d689f1b05c74fd008c67ae@haskell.org> Message-ID: <062.b0d131773b5acd6a8a31772abfc00737@haskell.org> #12365: Update documentation for partial type signatures -------------------------------------+------------------------------------- Reporter: goldfire | Owner: thomasw Type: bug | Status: merge Priority: normal | Milestone: 8.0.2 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:D2413 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => merge * milestone: => 8.0.2 Comment: Thanks thomasw! -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 20 15:41:45 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 20 Jul 2016 15:41:45 -0000 Subject: [GHC] #11357: Regression when deriving Generic1 on poly-kinded data family In-Reply-To: <050.901cd59cca6d2d30c1ece6815b80ca65@haskell.org> References: <050.901cd59cca6d2d30c1ece6815b80ca65@haskell.org> Message-ID: <065.9588b065588833a94f87c6958425d4e2@haskell.org> #11357: Regression when deriving Generic1 on poly-kinded data family -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: bug | Status: closed Priority: highest | Milestone: 8.0.1 Component: Compiler | Version: 7.11 (CodeGen) | Keywords: Generics, Resolution: fixed | TypeInType, TypeFamilies Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: GHC rejects | Test Case: valid program | deriving/should_compile/T11357 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): Oh dear, the commit mentioned in comment:15 is actually for #12357. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 20 15:42:51 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 20 Jul 2016 15:42:51 -0000 Subject: [GHC] #12357: Increasing maximum constraint tuple size significantly blows up compiler allocations In-Reply-To: <046.dd0f12e974ac3c5c9febd70397bf4138@haskell.org> References: <046.dd0f12e974ac3c5c9febd70397bf4138@haskell.org> Message-ID: <061.47e233aca9534649eefc65880c42e775@haskell.org> #12357: Increasing maximum constraint tuple size significantly blows up compiler allocations -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: bug | Status: patch Priority: normal | Milestone: Component: Compiler | Version: 7.10.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:D2400, Wiki Page: | Phab:D2414 -------------------------------------+------------------------------------- Comment (by bgamari): Sadly I mentioned the wrong commit in the commit message. Here is the merged commit for Phab:D2414, In [changeset:"9513fe6bdeafd35ca1a04e17b5f94732516766aa/ghc" 9513fe6/ghc]: {{{ Clean up interaction between name cache and built-in syntax This cleans up various aspects of the handling of built-in syntax in the original name cache (hopefully resulting in a nice reduction in compiler allocations), * Remove tuple types from original name cache: There is really no reason for these to be in the name cache since we already handle them specially in interface files to ensure that we can resolve them directly to Names, avoiding extraneous name cache lookups. * Sadly it's not possible to remove all traces of tuples from the name cache, however. Namely we need to keep the tuple type representations in since otherwise they would need to be wired-in * Remove the special cases for (:), [], and (##) in isBuiltInOcc_maybe and rename it to isTupleOcc_maybe * Split lookupOrigNameCache into two variants, * lookupOrigNameCache': Merely looks up an OccName in the original name cache, making no attempt to resolve tuples * lookupOrigNameCache: Like the above but handles tuples as well. This is given the un-primed name since it does the "obvious" thing from the perspective of an API user, who knows nothing of our special treatment of tuples. Arriving at this design took a significant amount of iteration. The trail of debris leading here can be found in #11357. Thanks to ezyang and Simon for all of their help in coming to this solution. Test Plan: Validate Reviewers: goldfire, simonpj, austin Reviewed By: simonpj Subscribers: thomie, ezyang Differential Revision: https://phabricator.haskell.org/D2414 GHC Trac Issues: #11357 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 20 16:06:29 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 20 Jul 2016 16:06:29 -0000 Subject: [GHC] #12062: Parallel make with -j0 and hs-boot leads to floating point exception In-Reply-To: <045.f05741a711c24d381cb39c4a23db2a0e@haskell.org> References: <045.f05741a711c24d381cb39c4a23db2a0e@haskell.org> Message-ID: <060.f651dc953cb125a7aaa52c4ffc3f1649@haskell.org> #12062: Parallel make with -j0 and hs-boot leads to floating point exception -------------------------------------+------------------------------------- Reporter: ezyang | Owner: petercommand Type: bug | Status: new Priority: low | Milestone: Component: Runtime System | Version: 8.0.1-rc2 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): D2415 Wiki Page: | -------------------------------------+------------------------------------- Changes (by petercommand): * differential: => D2415 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 20 16:07:15 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 20 Jul 2016 16:07:15 -0000 Subject: [GHC] #12413: Compact regions support needs some discussion in the release notes Message-ID: <046.9aceaa22b70735e95693c6721c17ff03@haskell.org> #12413: Compact regions support needs some discussion in the release notes -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: task | Status: new Priority: highest | Milestone: 8.2.1 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: -------------------------------------+------------------------------------- And perhaps elsewhere in the users guide. It was merged as cf989ffe490c146be4ed0fd7e0c00d3ff8fe1453. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 20 16:12:31 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 20 Jul 2016 16:12:31 -0000 Subject: [GHC] #12062: Parallel make with -j0 and hs-boot leads to floating point exception In-Reply-To: <045.f05741a711c24d381cb39c4a23db2a0e@haskell.org> References: <045.f05741a711c24d381cb39c4a23db2a0e@haskell.org> Message-ID: <060.a775e75865eb062297caf4ee0f0dad20@haskell.org> #12062: Parallel make with -j0 and hs-boot leads to floating point exception -------------------------------------+------------------------------------- Reporter: ezyang | Owner: petercommand Type: bug | Status: new Priority: low | Milestone: Component: Runtime System | Version: 8.0.1-rc2 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:D2415 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * differential: D2415 => Phab:D2415 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 20 16:12:40 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 20 Jul 2016 16:12:40 -0000 Subject: [GHC] #12062: Parallel make with -j0 and hs-boot leads to floating point exception In-Reply-To: <045.f05741a711c24d381cb39c4a23db2a0e@haskell.org> References: <045.f05741a711c24d381cb39c4a23db2a0e@haskell.org> Message-ID: <060.a5fabc380c144c83716b749fb44dbe1c@haskell.org> #12062: Parallel make with -j0 and hs-boot leads to floating point exception -------------------------------------+------------------------------------- Reporter: ezyang | Owner: petercommand Type: bug | Status: patch Priority: low | Milestone: Component: Runtime System | Version: 8.0.1-rc2 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:D2415 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => patch -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 20 16:27:13 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 20 Jul 2016 16:27:13 -0000 Subject: [GHC] #12169: libraries/base/dist-install/build/HSbase-4.9.0.0.o: unknown symbol `stat' In-Reply-To: <045.2c9db80d5b79d29cf709346ae32b99ef@haskell.org> References: <045.2c9db80d5b79d29cf709346ae32b99ef@haskell.org> Message-ID: <060.3853a8e042f609376e84ab6dafa00b6d@haskell.org> #12169: libraries/base/dist-install/build/HSbase-4.9.0.0.o: unknown symbol `stat' -------------------------------------+------------------------------------- Reporter: thomie | Owner: 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 rwbarton): https://www.redhat.com/archives/pam-list/1999-February/msg00082.html has the answer. Apparently little has changed in 17 years. What's happening is * `libc.so.6` defines only `__xstat`, not `stat`. * `sys/stat.h` defines `stat` as an extern inline function that calls `__xstat`. With optimizations enabled, gcc expands the inline function call to its definition, so it generates a reference to `__xstat` and that's that. * `libc.so` is a linker script that pulls in `libc.so.6` and `libc_nonshared.a`. The latter library contains the standalone definition of the function `stat` that a C program compiled without optimizations will be linked against. * If you link something with gcc then it will automatically link in `-lc`, because gcc is a C compiler. However if you link a shared library manually using `ld -shared` then ld will not add `-lc`, because ld is not a "C linker". This usually works okay in practice anyways, because you are linking or `dlopen()`ing the shared library into a C program. In the `dlopen()` case, the shared library can see the parts of the C library that are in `libc.so.6`, but not the parts that are in `libc_nonshared.a`. This is the problem in that email thread. In our case we use `ld -r` to combine all the object files for the `base` library into one `.o` file for faster loading into the RTS linker. I don't know whether there is an equivalent to `-lc` here that will also link in just the needed bits of `libc_nonshared.a`. Even the entirety of `libc_nonshared.a` is quite small (22K), but in my attempts I could only get ld to link against the entire static `libc.a`, which is unacceptable. One thing that would work is to load `libc_nonshared.a` into the RTS linker at startup time, but that's probably glibc-specific. Trying to parse the linker script `libc.so` sounds like a rabbit hole. As a hack, we could also just add `stat` and whatever else we need to `RtsSymbols.c`. (Or ideally, just deprecate the RTS linker...) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 20 17:25:35 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 20 Jul 2016 17:25:35 -0000 Subject: [GHC] #12414: Ill-formed or incorrect multiline string in compiler/main/GHC.hs Message-ID: <049.37c71e05bd988f351b404e104ad87fa6@haskell.org> #12414: Ill-formed or incorrect multiline string in compiler/main/GHC.hs -------------------------------------+------------------------------------- Reporter: ifigueroap | Owner: Type: bug | Status: new Priority: lowest | Milestone: Component: Compiler | Version: 8.0.1 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: Other Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- Dear all, After trying to (indirectly) parse GHC.hs using hothasktags, I kept getting an "Illegal character in string gap" error. After reconstructing the file using cpphs I found that the issue is caused by an incorrect multiline string in the raw (i.e. before cpp includes) GHC.hs, that trips the (perhaps stricter?) parser in haskell-src-exts... The following part of the code: {{{#!hs Nothing -> panic "compileToCoreModule: target FilePath not found in\ module dependency graph" }}} should be {{{#!hs Nothing -> panic "compileToCoreModule: target FilePath not found in\ \module dependency graph" }}} It seems the issue goes back to several other versions of the file. Of course it is not really a big deal, but it was hard to trigger (try to parse the file with haskell-src-exts), and to hunt!! Best regards -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 20 17:26:45 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 20 Jul 2016 17:26:45 -0000 Subject: [GHC] #12415: Fancy BinIface encoding for tuples is broken for constraint tuples Message-ID: <046.36b5b84566124dc8ed2f6851c925d504@haskell.org> #12415: Fancy BinIface encoding for tuples is broken for constraint tuples -------------------------------------+------------------------------------- Reporter: bgamari | Owner: 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: #12357 Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- We have a special way of encoding tuple-related names in the interface file symbol table. See `Note [Symbol table representation of names]`. However, it was broken for constraint tuples by ffc21506894c7887d3620423aaf86bc6113a1071. The problem is very similar to the one which prevented us from encoding tuple type representations in #12357 (see ticket:12357#comment:31). By unwiring constraint tuples it becomes harder to identify them for special handling during serialization. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 20 17:28:08 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 20 Jul 2016 17:28:08 -0000 Subject: [GHC] #12415: Fancy BinIface encoding for tuples is broken for constraint tuples In-Reply-To: <046.36b5b84566124dc8ed2f6851c925d504@haskell.org> References: <046.36b5b84566124dc8ed2f6851c925d504@haskell.org> Message-ID: <061.4322608edaa94d5adb5dec2485f38fa4@haskell.org> #12415: Fancy BinIface encoding for tuples is broken for constraint tuples -------------------------------------+------------------------------------- Reporter: bgamari | Owner: 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: #12357 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Description changed by bgamari: @@ -5,4 +5,22 @@ - ffc21506894c7887d3620423aaf86bc6113a1071. The problem is very similar to - the one which prevented us from encoding tuple type representations in - #12357 (see ticket:12357#comment:31). By unwiring constraint tuples it - becomes harder to identify them for special handling during serialization. + ffc21506894c7887d3620423aaf86bc6113a1071. Namely, `putName` now panics + when given a constraint tuple, + {{{#!hs + putTupleName_ :: BinHandle -> TyCon -> TupleSort -> Word32 -> IO () + putTupleName_ bh tc tup_sort thing_tag + = -- ASSERT(arity < 2^(30 :: Int)) + put_ bh (0x80000000 .|. (sort_tag `shiftL` 28) .|. (thing_tag `shiftL` + 26) .|. arity) + where + (sort_tag, arity) = case tup_sort of + BoxedTuple -> (0, fromIntegral (tyConArity tc)) + UnboxedTuple -> (1, fromIntegral (tyConArity tc `div` 2)) + -- See Note [Unboxed tuple RuntimeRep vars] in TyCon + ConstraintTuple -> pprPanic "putTupleName:ConstraintTuple" (ppr tc) + }}} + While this currently doesn't break anything, this is only because the + clever encoding isn't used for constraint tuples. + + I believe the problem is very similar to the one which prevented us from + encoding tuple type representations in #12357 (see + ticket:12357#comment:31). By unwiring constraint tuples it becomes harder + to identify them for special handling during serialization. New description: We have a special way of encoding tuple-related names in the interface file symbol table. See `Note [Symbol table representation of names]`. However, it was broken for constraint tuples by ffc21506894c7887d3620423aaf86bc6113a1071. Namely, `putName` now panics when given a constraint tuple, {{{#!hs putTupleName_ :: BinHandle -> TyCon -> TupleSort -> Word32 -> IO () putTupleName_ bh tc tup_sort thing_tag = -- ASSERT(arity < 2^(30 :: Int)) put_ bh (0x80000000 .|. (sort_tag `shiftL` 28) .|. (thing_tag `shiftL` 26) .|. arity) where (sort_tag, arity) = case tup_sort of BoxedTuple -> (0, fromIntegral (tyConArity tc)) UnboxedTuple -> (1, fromIntegral (tyConArity tc `div` 2)) -- See Note [Unboxed tuple RuntimeRep vars] in TyCon ConstraintTuple -> pprPanic "putTupleName:ConstraintTuple" (ppr tc) }}} While this currently doesn't break anything, this is only because the clever encoding isn't used for constraint tuples. I believe the problem is very similar to the one which prevented us from encoding tuple type representations in #12357 (see ticket:12357#comment:31). By unwiring constraint tuples it becomes harder to identify them for special handling during serialization. -- -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 20 17:29:41 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 20 Jul 2016 17:29:41 -0000 Subject: [GHC] #12415: Fancy BinIface encoding for tuples is broken for constraint tuples In-Reply-To: <046.36b5b84566124dc8ed2f6851c925d504@haskell.org> References: <046.36b5b84566124dc8ed2f6851c925d504@haskell.org> Message-ID: <061.2faa24910a61c6bf724a7aa2c3a8f8b6@haskell.org> #12415: Fancy BinIface encoding for tuples is broken for constraint tuples -------------------------------------+------------------------------------- Reporter: bgamari | Owner: 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: #12357 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Description changed by bgamari: @@ -26,1 +26,2 @@ - to identify them for special handling during serialization. + to identify them for special handling during serialization, when we only + have the `Name` to look at. New description: We have a special way of encoding tuple-related names in the interface file symbol table. See `Note [Symbol table representation of names]`. However, it was broken for constraint tuples by ffc21506894c7887d3620423aaf86bc6113a1071. Namely, `putName` now panics when given a constraint tuple, {{{#!hs putTupleName_ :: BinHandle -> TyCon -> TupleSort -> Word32 -> IO () putTupleName_ bh tc tup_sort thing_tag = -- ASSERT(arity < 2^(30 :: Int)) put_ bh (0x80000000 .|. (sort_tag `shiftL` 28) .|. (thing_tag `shiftL` 26) .|. arity) where (sort_tag, arity) = case tup_sort of BoxedTuple -> (0, fromIntegral (tyConArity tc)) UnboxedTuple -> (1, fromIntegral (tyConArity tc `div` 2)) -- See Note [Unboxed tuple RuntimeRep vars] in TyCon ConstraintTuple -> pprPanic "putTupleName:ConstraintTuple" (ppr tc) }}} While this currently doesn't break anything, this is only because the clever encoding isn't used for constraint tuples. I believe the problem is very similar to the one which prevented us from encoding tuple type representations in #12357 (see ticket:12357#comment:31). By unwiring constraint tuples it becomes harder to identify them for special handling during serialization, when we only have the `Name` to look at. -- -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 20 20:53:40 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 20 Jul 2016 20:53:40 -0000 Subject: [GHC] #12414: Ill-formed or incorrect multiline string in compiler/main/GHC.hs In-Reply-To: <049.37c71e05bd988f351b404e104ad87fa6@haskell.org> References: <049.37c71e05bd988f351b404e104ad87fa6@haskell.org> Message-ID: <064.95b593a11a4fe794a9e33a0396d3e14a@haskell.org> #12414: Ill-formed or incorrect multiline string in compiler/main/GHC.hs -------------------------------------+------------------------------------- Reporter: ifigueroap | Owner: Type: bug | Status: new Priority: lowest | Milestone: Component: Compiler | Version: 8.0.1 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 osa1): This looks like a bug in the parser -- this string should be rejected according to Haskell2010. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 20 21:05:21 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 20 Jul 2016 21:05:21 -0000 Subject: [GHC] #12414: Ill-formed or incorrect multiline string in compiler/main/GHC.hs In-Reply-To: <049.37c71e05bd988f351b404e104ad87fa6@haskell.org> References: <049.37c71e05bd988f351b404e104ad87fa6@haskell.org> Message-ID: <064.1308c4069cb4cffcf385bf8cab468d9a@haskell.org> #12414: Ill-formed or incorrect multiline string in compiler/main/GHC.hs -------------------------------------+------------------------------------- Reporter: ifigueroap | Owner: Type: bug | Status: new Priority: lowest | Milestone: Component: Compiler | Version: 8.0.1 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 ifigueroap): Replying to [comment:1 osa1]: > This looks like a bug in the parser -- this string should be rejected according to Haskell2010. You mean a bug in the internal ghc parser, right? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 20 21:18:01 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 20 Jul 2016 21:18:01 -0000 Subject: [GHC] #12414: Ill-formed or incorrect multiline string in compiler/main/GHC.hs In-Reply-To: <049.37c71e05bd988f351b404e104ad87fa6@haskell.org> References: <049.37c71e05bd988f351b404e104ad87fa6@haskell.org> Message-ID: <064.bbe53258853207e010b683a6d858bfd7@haskell.org> #12414: Ill-formed or incorrect multiline string in compiler/main/GHC.hs -------------------------------------+------------------------------------- Reporter: ifigueroap | Owner: Type: bug | Status: new Priority: lowest | Milestone: Component: Compiler | Version: 8.0.1 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 osa1): Yes, from Haskell2010 says this: (https://www.haskell.org/onlinereport/haskell2010/haskellch2.html#x7-200002.6) > A string may include a “gap”—two backslants enclosing white characters—which is ignored. This allows one to write long strings on more than one line by writing a backslant at the end of one line and at the start of the next. It seems like we don't follow this rule, we only have one backslash here. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 20 21:20:50 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 20 Jul 2016 21:20:50 -0000 Subject: [GHC] #12414: Ill-formed or incorrect multiline string in compiler/main/GHC.hs In-Reply-To: <049.37c71e05bd988f351b404e104ad87fa6@haskell.org> References: <049.37c71e05bd988f351b404e104ad87fa6@haskell.org> Message-ID: <064.7e478dccf42d42dfef67b3784002c6f7@haskell.org> #12414: Ill-formed or incorrect multiline string in compiler/main/GHC.hs -------------------------------------+------------------------------------- Reporter: ifigueroap | Owner: Type: bug | Status: closed Priority: lowest | Milestone: Component: Compiler | Version: 8.0.1 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 rwbarton): * status: new => closed * resolution: => invalid Comment: No, it's correct as-is. The C preprocessor consumes the line continuation marker `\`, so the Haskell source is a single-line string constant. It would be wrong to add a second `\` before `module`. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 20 21:29:53 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 20 Jul 2016 21:29:53 -0000 Subject: [GHC] #12414: Ill-formed or incorrect multiline string in compiler/main/GHC.hs In-Reply-To: <049.37c71e05bd988f351b404e104ad87fa6@haskell.org> References: <049.37c71e05bd988f351b404e104ad87fa6@haskell.org> Message-ID: <064.3a8fdb56608f90a2d28c1442b03af197@haskell.org> #12414: Ill-formed or incorrect multiline string in compiler/main/GHC.hs -------------------------------------+------------------------------------- Reporter: ifigueroap | Owner: Type: bug | Status: closed Priority: lowest | Milestone: Component: Compiler | Version: 8.0.1 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 ifigueroap): * Attachment "GHC.hs" added. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 20 21:31:57 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 20 Jul 2016 21:31:57 -0000 Subject: [GHC] #12414: Ill-formed or incorrect multiline string in compiler/main/GHC.hs In-Reply-To: <049.37c71e05bd988f351b404e104ad87fa6@haskell.org> References: <049.37c71e05bd988f351b404e104ad87fa6@haskell.org> Message-ID: <064.698665fb2f8bc2e635af30b111532b8b@haskell.org> #12414: Ill-formed or incorrect multiline string in compiler/main/GHC.hs -------------------------------------+------------------------------------- Reporter: ifigueroap | Owner: Type: bug | Status: closed Priority: lowest | Milestone: Component: Compiler | Version: 8.0.1 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: | -------------------------------------+------------------------------------- Comment (by ifigueroap): I just attached the file produced when building ghc-8.0.1 from github. I cloned the repo, fixed the package-library redirects, and then performed ./boot, configure and make. The particular string I point in this issue is located in line 1021 and continues in line 1022. Perhaps I'm doing something wrong when building? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 20 21:38:00 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 20 Jul 2016 21:38:00 -0000 Subject: [GHC] #12414: Ill-formed or incorrect multiline string in compiler/main/GHC.hs In-Reply-To: <049.37c71e05bd988f351b404e104ad87fa6@haskell.org> References: <049.37c71e05bd988f351b404e104ad87fa6@haskell.org> Message-ID: <064.4e0c92562f8348e0e79e9fd50d32b624@haskell.org> #12414: Ill-formed or incorrect multiline string in compiler/main/GHC.hs -------------------------------------+------------------------------------- Reporter: ifigueroap | Owner: Type: bug | Status: closed Priority: lowest | Milestone: Component: Compiler | Version: 8.0.1 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: | -------------------------------------+------------------------------------- Comment (by rwbarton): I don't understand the question...? That is a source file, it is not produced by anything. GHC automatically runs it through CPP before compiling, because it has `{-# LANGUAGE CPP #-}`. The output of CPP is a valid Haskell module. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 20 21:50:06 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 20 Jul 2016 21:50:06 -0000 Subject: [GHC] #12414: Ill-formed or incorrect multiline string in compiler/main/GHC.hs In-Reply-To: <049.37c71e05bd988f351b404e104ad87fa6@haskell.org> References: <049.37c71e05bd988f351b404e104ad87fa6@haskell.org> Message-ID: <064.138d620f3069002d1502e8d0d4698e06@haskell.org> #12414: Ill-formed or incorrect multiline string in compiler/main/GHC.hs -------------------------------------+------------------------------------- Reporter: ifigueroap | Owner: Type: bug | Status: closed Priority: lowest | Milestone: Component: Compiler | Version: 8.0.1 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: | -------------------------------------+------------------------------------- Comment (by ifigueroap): Replying to [comment:6 rwbarton]: > I don't understand the question...? That is a source file, it is not produced by anything. GHC automatically runs it through CPP before compiling, because it has `{-# LANGUAGE CPP #-}`. The output of CPP is a valid Haskell module. Well, my point is that when running hothasktags, which internally runs cpphs and then tries to parse with haskell-src-exts I get the aforementioned "Illegal character in string gap", ''which in this particular case may mean that the output of the preprocessor is not a valid Haskell module.'' I'm not sure whether this is the case in the build process, as I didn't find how to get the post-processed file during compilation. To illustrate my point, if I manually run the preprocessor (in the compiler/main dir): {{{ cpphs -I../ -I../stage1 GHC.hs > GHC2.hs }}} (Note the two includes are for HsVersions.h in compiler/ and for ghc_autoconf.h in compiler/stage1). I get the "ill-formed" two-line string in the resulting GHC2.hs file. Of course I'm not sure what other flags are being passed to cpphs... -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 20 21:51:00 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 20 Jul 2016 21:51:00 -0000 Subject: [GHC] #12414: Ill-formed or incorrect multiline string in compiler/main/GHC.hs In-Reply-To: <049.37c71e05bd988f351b404e104ad87fa6@haskell.org> References: <049.37c71e05bd988f351b404e104ad87fa6@haskell.org> Message-ID: <064.ec0dbadcb6ec1f5bba2a8c66da30cc3f@haskell.org> #12414: Ill-formed or incorrect multiline string in compiler/main/GHC.hs -------------------------------------+------------------------------------- Reporter: ifigueroap | Owner: Type: bug | Status: closed Priority: lowest | Milestone: Component: Compiler | Version: 8.0.1 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 ifigueroap): * Attachment "GHC.hs" added. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 20 21:51:00 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 20 Jul 2016 21:51:00 -0000 Subject: [GHC] #12414: Ill-formed or incorrect multiline string in compiler/main/GHC.hs In-Reply-To: <049.37c71e05bd988f351b404e104ad87fa6@haskell.org> References: <049.37c71e05bd988f351b404e104ad87fa6@haskell.org> Message-ID: <064.3a8fdb56608f90a2d28c1442b03af197@haskell.org> #12414: Ill-formed or incorrect multiline string in compiler/main/GHC.hs -------------------------------------+------------------------------------- Reporter: ifigueroap | Owner: Type: bug | Status: closed Priority: lowest | Milestone: Component: Compiler | Version: 8.0.1 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 ifigueroap): * Attachment "GHC.hs" removed. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 20 21:51:22 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 20 Jul 2016 21:51:22 -0000 Subject: [GHC] #12414: Ill-formed or incorrect multiline string in compiler/main/GHC.hs In-Reply-To: <049.37c71e05bd988f351b404e104ad87fa6@haskell.org> References: <049.37c71e05bd988f351b404e104ad87fa6@haskell.org> Message-ID: <064.e2d5bb7975c6f59a68321ac3a7ca375d@haskell.org> #12414: Ill-formed or incorrect multiline string in compiler/main/GHC.hs -------------------------------------+------------------------------------- Reporter: ifigueroap | Owner: Type: bug | Status: closed Priority: lowest | Milestone: Component: Compiler | Version: 8.0.1 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 ifigueroap): * Attachment "GHC2.hs" added. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 20 22:02:22 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 20 Jul 2016 22:02:22 -0000 Subject: [GHC] #12414: Ill-formed or incorrect multiline string in compiler/main/GHC.hs In-Reply-To: <049.37c71e05bd988f351b404e104ad87fa6@haskell.org> References: <049.37c71e05bd988f351b404e104ad87fa6@haskell.org> Message-ID: <064.21266958979f20e52020841e633bbf7d@haskell.org> #12414: Ill-formed or incorrect multiline string in compiler/main/GHC.hs -------------------------------------+------------------------------------- Reporter: ifigueroap | Owner: Type: bug | Status: closed Priority: lowest | Milestone: Component: Compiler | Version: 8.0.1 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: | -------------------------------------+------------------------------------- Comment (by rwbarton): Oh, cpphs doesn't seem to understand the line continuation syntax. I guess you need a real C preprocessor. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 20 22:31:49 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 20 Jul 2016 22:31:49 -0000 Subject: [GHC] #12414: Ill-formed or incorrect multiline string in compiler/main/GHC.hs In-Reply-To: <049.37c71e05bd988f351b404e104ad87fa6@haskell.org> References: <049.37c71e05bd988f351b404e104ad87fa6@haskell.org> Message-ID: <064.b1082ad9f6628e3a3d7ef543763163bd@haskell.org> #12414: Ill-formed or incorrect multiline string in compiler/main/GHC.hs -------------------------------------+------------------------------------- Reporter: ifigueroap | Owner: Type: bug | Status: closed Priority: lowest | Milestone: Component: Compiler | Version: 8.0.1 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: | -------------------------------------+------------------------------------- Comment (by ifigueroap): Replying to [comment:8 rwbarton]: > Oh, cpphs doesn't seem to understand the line continuation syntax. I guess you need a real C preprocessor. Thanks, you are right, I just run {{{ gcc -E -I../ -I../stage1 GHC.c }}} (with a dirty rename to .c) in order to use a real C preprocessor, and althought I got several errorrs, the particular string is now in 1 line. Thanks! -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 20 22:58:25 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 20 Jul 2016 22:58:25 -0000 Subject: [GHC] #11771: ghc.exe: `panic'! (the 'impossible' happened); thread blocked indefinitely in an MVar operation In-Reply-To: <048.fac6b544c2d3d144dfdcb6fd33b2e2c7@haskell.org> References: <048.fac6b544c2d3d144dfdcb6fd33b2e2c7@haskell.org> Message-ID: <063.4a901a55e6f0bf182dd6384e3903ba75@haskell.org> #11771: ghc.exe: `panic'! (the 'impossible' happened); thread blocked indefinitely in an MVar operation -------------------------------+---------------------------------------- Reporter: YoYoYonnY | Owner: Type: bug | Status: new Priority: low | Milestone: Component: GHCi | Version: 7.10.3 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 itaibn): I had a similar crash in GHC 7.4.1. Also can't replicate. Full session: {{{ GHCi, version 7.4.1: 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> 2**9 512.0 Prelude> 2^9 512 Prelude> 9^9 387420489 Prelude> 9^9^9 ^C^C^C^C^C^C^C^C^C^C^CcInterPrelude> Prelude> ghc: panic! (the 'impossible' happened) (GHC version 7.4.1 for x86_64-unknown-linux): thread blocked indefinitely in an MVar operation 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 Thu Jul 21 07:36:11 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 21 Jul 2016 07:36:11 -0000 Subject: [GHC] #12416: Some GCC versions warn about failed inlines Message-ID: <046.adef2f266c45a6c2f2bf6b2786766339@haskell.org> #12416: Some GCC versions warn about failed inlines -------------------------------------+------------------------------------- Reporter: bgamari | Owner: 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: -------------------------------------+------------------------------------- gcc 4.8.4 on Ubuntu 14.04 warns about failed inlinings. I'm not really sure what to do about this at the moment, so I'm going to leave this here. {{{ In file included from rts/Schedule.h:15:0: error: 0, from rts/Capability.c:23: In function ‘initCapability’: rts/Trace.h:742:20: error: warning: inlining failed in call to ‘traceSparkCounters.part.10’: call is unlikely and code size would grow [-Winline] INLINE_HEADER void traceSparkCounters(Capability *cap STG_UNUSED) ^ cc1: warning: called from here [-Winline] In function ‘yieldCapability’: rts/Trace.h:742:20: error: warning: inlining failed in call to ‘traceSparkCounters.part.10’: call is unlikely and code size would grow [-Winline] INLINE_HEADER void traceSparkCounters(Capability *cap STG_UNUSED) ^ cc1: warning: called from here [-Winline] In function ‘shutdownCapabilities’: rts/Trace.h:742:20: error: warning: inlining failed in call to ‘traceSparkCounters.part.10’: call is unlikely and code size would grow [-Winline] INLINE_HEADER void traceSparkCounters(Capability *cap STG_UNUSED) ^ cc1: warning: called from here [-Winline] }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 21 08:12:23 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 21 Jul 2016 08:12:23 -0000 Subject: [GHC] #12375: type synonym to unboxed tuple causes crash In-Reply-To: <043.ec186c470be76b29348c4afe9786397d@haskell.org> References: <043.ec186c470be76b29348c4afe9786397d@haskell.org> Message-ID: <058.b791578c2a0320a643be66f7c40bed1f@haskell.org> #12375: type synonym to unboxed tuple causes crash -------------------------------------+------------------------------------- Reporter: osa1 | Owner: 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 Ömer Sinan Ağacan ): In [changeset:"714bebff44076061d0a719c4eda2cfd213b7ac3d/ghc" 714bebf/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="714bebff44076061d0a719c4eda2cfd213b7ac3d" Implement unboxed sum primitive type Summary: This patch implements primitive unboxed sum types, as described in https://ghc.haskell.org/trac/ghc/wiki/UnpackedSumTypes. Main changes are: - Add new syntax for unboxed sums types, terms and patterns. Hidden behind `-XUnboxedSums`. - Add unlifted unboxed sum type constructors and data constructors, extend type and pattern checkers and desugarer. - Add new RuntimeRep for unboxed sums. - Extend unarise pass to translate unboxed sums to unboxed tuples right before code generation. - Add `StgRubbishArg` to `StgArg`, and a new type `CmmArg` for better code generation when sum values are involved. - Add user manual section for unboxed sums. Some other changes: - Generalize `UbxTupleRep` to `MultiRep` and `UbxTupAlt` to `MultiValAlt` to be able to use those with both sums and tuples. - Don't use `tyConPrimRep` in `isVoidTy`: `tyConPrimRep` is really wrong, given an `Any` `TyCon`, there's no way to tell what its kind is, but `kindPrimRep` and in turn `tyConPrimRep` returns `PtrRep`. - Fix some bugs on the way: #12375. Not included in this patch: - Update Haddock for new the new unboxed sum syntax. - `TemplateHaskell` support is left as future work. For reviewers: - Front-end code is mostly trivial and adapted from unboxed tuple code for type checking, pattern checking, renaming, desugaring etc. - Main translation routines are in `RepType` and `UnariseStg`. Documentation in `UnariseStg` should be enough for understanding what's going on. Credits: - Johan Tibell wrote the initial front-end and interface file extensions. - Simon Peyton Jones reviewed this patch many times, wrote some code, and helped with debugging. Reviewers: bgamari, alanz, goldfire, RyanGlScott, simonpj, austin, simonmar, hvr, erikd Reviewed By: simonpj Subscribers: Iceland_jack, ggreif, ezyang, RyanGlScott, goldfire, thomie, mpickering Differential Revision: https://phabricator.haskell.org/D2259 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 21 08:24:09 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 21 Jul 2016 08:24:09 -0000 Subject: [GHC] #12417: API annotations for unboxed sums needs reworking Message-ID: <043.00b31e92686f5920efa6f831cd588891@haskell.org> #12417: API annotations for unboxed sums needs reworking -------------------------------------+------------------------------------- Reporter: osa1 | Owner: 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: -------------------------------------+------------------------------------- API annotations for unboxed sums are not entirely correct. As far as I understand, some of the bars (`|`) in the concrete syntax are not properly attached to any of the AST nodes. Some discussion can be seen in [https://phabricator.haskell.org/D2259#69809 the Phab page]. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 21 08:32:40 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 21 Jul 2016 08:32:40 -0000 Subject: [GHC] #12417: API annotations for unboxed sums needs reworking In-Reply-To: <043.00b31e92686f5920efa6f831cd588891@haskell.org> References: <043.00b31e92686f5920efa6f831cd588891@haskell.org> Message-ID: <058.ea5b089170bb62685f4cc1cc6881a77b@haskell.org> #12417: API annotations for unboxed sums needs reworking -------------------------------------+------------------------------------- Reporter: osa1 | Owner: alanz Type: bug | Status: new Priority: normal | Milestone: 8.2.1 Component: Compiler | Version: 8.1 (Parser) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect API | Unknown/Multiple annotation | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by alanz): * owner: => alanz * failure: None/Unknown => Incorrect API annotation * version: 8.0.1 => 8.1 * component: Compiler => Compiler (Parser) * milestone: => 8.2.1 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 21 08:55:03 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 21 Jul 2016 08:55:03 -0000 Subject: [GHC] #10547: feature request: expanding type synonyms in error messages In-Reply-To: <043.c20ed6dece31f72a0d7c2a22033dd48e@haskell.org> References: <043.c20ed6dece31f72a0d7c2a22033dd48e@haskell.org> Message-ID: <058.b4fcc5c8f8e4e20008f3b7705662dca8@haskell.org> #10547: feature request: expanding type synonyms in error messages -------------------------------------+------------------------------------- Reporter: osa1 | Owner: Type: feature request | Status: merge Priority: low | Milestone: 8.0.2 Component: Compiler (Type | Version: checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | typecheck/should_fail/ExpandSynsFail1,2,3,4 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D1016, Wiki Page: | Phab:D2198 -------------------------------------+------------------------------------- Changes (by osa1): * status: new => merge -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 21 08:55:56 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 21 Jul 2016 08:55:56 -0000 Subject: [GHC] #12116: No easy way to add cost-centre to top-levels In-Reply-To: <043.6b04c4666f71935c9beabebf233c1a73@haskell.org> References: <043.6b04c4666f71935c9beabebf233c1a73@haskell.org> Message-ID: <058.5ca61b542d09a2637c4e59d8a65d8aed@haskell.org> #12116: No easy way to add cost-centre to top-levels -------------------------------------+------------------------------------- Reporter: osa1 | Owner: Type: feature request | Status: merge 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): Phab:D2407 Wiki Page: | -------------------------------------+------------------------------------- Changes (by osa1): * status: new => merge * differential: => Phab:D2407 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 21 09:37:19 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 21 Jul 2016 09:37:19 -0000 Subject: [GHC] #12413: Compact regions support needs some discussion in the release notes In-Reply-To: <046.9aceaa22b70735e95693c6721c17ff03@haskell.org> References: <046.9aceaa22b70735e95693c6721c17ff03@haskell.org> Message-ID: <061.47aaaad54e5f4b97dba3b8a4e3c0283b@haskell.org> #12413: Compact regions support needs some discussion in the release notes -------------------------------------+------------------------------------- Reporter: bgamari | Owner: simonmar Type: task | Status: new Priority: highest | Milestone: 8.2.1 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: | -------------------------------------+------------------------------------- Changes (by simonmar): * owner: => simonmar -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 21 09:49:17 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 21 Jul 2016 09:49:17 -0000 Subject: [GHC] #12416: Some GCC versions warn about failed inlines In-Reply-To: <046.adef2f266c45a6c2f2bf6b2786766339@haskell.org> References: <046.adef2f266c45a6c2f2bf6b2786766339@haskell.org> Message-ID: <061.47cbb479e13fe7e182ac7fe741910b05@haskell.org> #12416: Some GCC versions warn about failed inlines -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: bug | Status: new 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): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonmar): The warnings don't cause a build failure, right? The fix is to make them EXTERN_INLINE instead. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 21 11:14:15 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 21 Jul 2016 11:14:15 -0000 Subject: [GHC] #7662: Improve GC of mutable objects In-Reply-To: <045.1df59d879ca14d9200a5a4cc6e9474e1@haskell.org> References: <045.1df59d879ca14d9200a5a4cc6e9474e1@haskell.org> Message-ID: <060.2a0970b2f0ceeb0412a4666166fabef5@haskell.org> #7662: Improve GC of mutable objects -------------------------------------+------------------------------------- Reporter: ezyang | Owner: Type: feature request | Status: new Priority: normal | Milestone: ⊥ Component: Runtime System | Version: 7.7 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 osa1): * cc: osa1 (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 21 11:34:45 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 21 Jul 2016 11:34:45 -0000 Subject: [GHC] #12414: Ill-formed or incorrect multiline string in compiler/main/GHC.hs In-Reply-To: <049.37c71e05bd988f351b404e104ad87fa6@haskell.org> References: <049.37c71e05bd988f351b404e104ad87fa6@haskell.org> Message-ID: <064.2da1bcc1b0c0c27f8eb6bad91b0b56fa@haskell.org> #12414: Ill-formed or incorrect multiline string in compiler/main/GHC.hs -------------------------------------+------------------------------------- Reporter: ifigueroap | Owner: Type: bug | Status: closed Priority: lowest | Milestone: Component: Compiler | Version: 8.0.1 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: | -------------------------------------+------------------------------------- Comment (by malcolmw): Indeed, cpphs only lexes the contents of CPP directives as C. It lexes all other text as Haskell. This is entirely intentional, and is designed to work around numerous issues people have with traditional cpp doing the wrong thing with otherwise-correct Haskell source. I would suggest that ghc source files should not be relying on these bad features of cpp. What next? /* */ style comments? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 21 13:36:20 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 21 Jul 2016 13:36:20 -0000 Subject: [GHC] #12377: getExecutablePath doesn't return absolute path on OpenBSD (and maybe other OS also) In-Reply-To: <047.ce292d74547e5761ab80fddf4c2b76fa@haskell.org> References: <047.ce292d74547e5761ab80fddf4c2b76fa@haskell.org> Message-ID: <062.3c9a7b51aea75d68183afaa23f284908@haskell.org> #12377: getExecutablePath doesn't return absolute path on OpenBSD (and maybe other OS also) -------------------------------------+------------------------------------- Reporter: oherrala | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: libraries/base | Version: 7.10.3 Resolution: | Keywords: Operating System: OpenBSD | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by thomie): Please send a patch, see [wiki:WorkingConventions/FixingBugs]. I don't think any of the regular contributors use OpenBSD. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 21 13:48:43 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 21 Jul 2016 13:48:43 -0000 Subject: [GHC] #12357: Increasing maximum constraint tuple size significantly blows up compiler allocations In-Reply-To: <046.dd0f12e974ac3c5c9febd70397bf4138@haskell.org> References: <046.dd0f12e974ac3c5c9febd70397bf4138@haskell.org> Message-ID: <061.d3e3ae4c3c9761b7911450162b88ff8b@haskell.org> #12357: Increasing maximum constraint tuple size significantly blows up compiler allocations -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: bug | Status: patch Priority: normal | Milestone: Component: Compiler | Version: 7.10.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:D2400, Wiki Page: | Phab:D2414 -------------------------------------+------------------------------------- Comment (by bgamari): Unfortunately I had to revert the above patch (in 83e4f49577665278fe08fbaafe2239553f3c448e) since it appears to break Haddock. This issue is now back on my queue -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 21 13:49:11 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 21 Jul 2016 13:49:11 -0000 Subject: [GHC] #12357: Increasing maximum constraint tuple size significantly blows up compiler allocations In-Reply-To: <046.dd0f12e974ac3c5c9febd70397bf4138@haskell.org> References: <046.dd0f12e974ac3c5c9febd70397bf4138@haskell.org> Message-ID: <061.d5c1feccde673894cdbd9186506b54af@haskell.org> #12357: Increasing maximum constraint tuple size significantly blows up compiler allocations -------------------------------------+------------------------------------- Reporter: bgamari | Owner: bgamari Type: bug | Status: patch Priority: normal | Milestone: Component: Compiler | Version: 7.10.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:D2400, Wiki Page: | Phab:D2414 -------------------------------------+------------------------------------- Changes (by bgamari): * owner: => bgamari -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 21 13:54:25 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 21 Jul 2016 13:54:25 -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.51945a7388a128bc1f4ef9b59fb35db0@haskell.org> #12379: WARN pragma gives warning `warning: [-Wdeprecations]' -------------------------------------+------------------------------------- Reporter: zilinc | Owner: Type: bug | Status: new Priority: low | Milestone: Component: Documentation | Version: 8.0.1 Resolution: | Keywords: Operating System: Linux | Architecture: x86_64 Type of failure: Documentation | (amd64) bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by thomie): * failure: Incorrect warning at compile-time => Documentation bug * component: Compiler => Documentation Comment: This commit explains it: 27abb1f52b023d7bc8a796e22e5e7ef281df0fcb {{{ Author: Simon Marlow Date: Tue Aug 12 14:16:06 2008 +0000 put back -fwarn-depcrecations It was replaced by -fwarn-warnings-deprecations, but I think we want to keep it for backwards compatibility. I'm not sure we want to deprecate it either... }}} So both flags exist, and the warning message happens to pick the shorter version. Just a documentation issue. For a newcomer: update `docs/users_guide/using-warnings.rst` and `utils/mkUserGuidePart/Options/Warnings.hs`. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 21 13:54:44 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 21 Jul 2016 13:54:44 -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.c8b712e1ba0a7a8ba29d93b43d93247d@haskell.org> #12379: WARN pragma gives warning `warning: [-Wdeprecations]' -------------------------------------+------------------------------------- Reporter: zilinc | Owner: Type: bug | Status: new Priority: low | 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 thomie): * keywords: => newcomer * os: Linux => Unknown/Multiple * architecture: x86_64 (amd64) => Unknown/Multiple -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 21 13:56:49 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 21 Jul 2016 13:56:49 -0000 Subject: [GHC] #12380: ghc: panic! (the 'impossible' happened) In-Reply-To: <047.e34a54a22884f581cc455807c95f0c38@haskell.org> References: <047.e34a54a22884f581cc455807c95f0c38@haskell.org> Message-ID: <062.041473efb6532bdb740e118462d739af@haskell.org> #12380: ghc: panic! (the 'impossible' happened) ---------------------------------+-------------------------------------- Reporter: Hassan58 | Owner: Type: bug | Status: infoneeded Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 Resolution: | 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: | ---------------------------------+-------------------------------------- Changes (by thomie): * status: new => infoneeded Comment: Hassan58: is the problem reproducible? Can you provide a way to reproduce it, preferably with a small program that doesn't have too many dependencies. Thanks. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 21 13:59:25 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 21 Jul 2016 13:59:25 -0000 Subject: [GHC] #12383: ghc: internal error: TSO object entered In-Reply-To: <047.4cc86cc0c137f15fdedd00b118aa1ed6@haskell.org> References: <047.4cc86cc0c137f15fdedd00b118aa1ed6@haskell.org> Message-ID: <062.9a1fa5cc6999bc5e51abf0b87dc1e608@haskell.org> #12383: ghc: internal error: TSO object entered -------------------------------------+------------------------------------- Reporter: aufheben | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Linux | Architecture: x86_64 Type of failure: Compile-time | (amd64) crash | Test Case: Blocked By: | Blocking: Related Tickets: #8316 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by thomie): * related: => #8316 Comment: Hopefully this is the same issue as #8316, which has a small testcase already. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 21 14:00:23 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 21 Jul 2016 14:00:23 -0000 Subject: [GHC] #12383: ghc: internal error: TSO object entered In-Reply-To: <047.4cc86cc0c137f15fdedd00b118aa1ed6@haskell.org> References: <047.4cc86cc0c137f15fdedd00b118aa1ed6@haskell.org> Message-ID: <062.682a45c21af1ffa8fc86ad30d9d64245@haskell.org> #12383: ghc: internal error: TSO object entered -------------------------------------+------------------------------------- Reporter: aufheben | Owner: Type: bug | Status: infoneeded Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Linux | Architecture: x86_64 Type of failure: Compile-time | (amd64) crash | Test Case: Blocked By: | Blocking: Related Tickets: #8316 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by thomie): * status: new => infoneeded -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 21 14:25:09 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 21 Jul 2016 14:25:09 -0000 Subject: [GHC] #12095: GHC and LLVM don't agree on what to do with byteSwap16# In-Reply-To: <052.819038532472d3051449ad4890ff8793@haskell.org> References: <052.819038532472d3051449ad4890ff8793@haskell.org> Message-ID: <067.8521d6427b04b1a237495b5375e05d0e@haskell.org> #12095: GHC and LLVM don't agree on what to do with byteSwap16# -------------------------------------+------------------------------------- Reporter: thoughtpolice | Owner: Type: bug | Status: closed Priority: high | Milestone: 8.0.2 Component: Compiler (LLVM) | Version: 8.0.1 Resolution: invalid | Keywords: codegen, llvm 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 thomie): * cc: tibbe, tab (added) * status: new => closed * resolution: => invalid Comment: CC @tab (Vincent Hanquez), who added these primops in 18087a119b47368b15231c43402c81888c75957d (#7902), and tibbe who reviewed them. Please see comment:2. > (it should probably go into another ticket and I should close this one.) Yes, please open a new (feature request) ticket if necessary. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 21 14:36:45 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 21 Jul 2016 14:36:45 -0000 Subject: [GHC] #12229: Narrow the scope of record wildcards notation slightly In-Reply-To: <046.d2c026a8bed745e3c7425028981b0442@haskell.org> References: <046.d2c026a8bed745e3c7425028981b0442@haskell.org> Message-ID: <061.225706d8134e9962457071581fce1cfe@haskell.org> #12229: Narrow the scope of record wildcards notation slightly -------------------------------------+------------------------------------- Reporter: simonpj | Owner: Type: bug | 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: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by thomie): * status: new => closed * resolution: => fixed * milestone: => 8.2.1 Comment: Closing, as the work is done here. Please leave a comment here or open a new ticket if this change of behavior bites you badly. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 21 14:42:16 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 21 Jul 2016 14:42:16 -0000 Subject: [GHC] #12375: type synonym to unboxed tuple causes crash In-Reply-To: <043.ec186c470be76b29348c4afe9786397d@haskell.org> References: <043.ec186c470be76b29348c4afe9786397d@haskell.org> Message-ID: <058.db016c67f05c529df315c71774ba0bfa@haskell.org> #12375: type synonym to unboxed tuple causes crash -------------------------------------+------------------------------------- Reporter: osa1 | Owner: 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 osa1): * status: new => closed * resolution: => fixed -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 21 14:56:00 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 21 Jul 2016 14:56:00 -0000 Subject: [GHC] #12368: Demand Analyzer: Cunnig plan not adhered to with aborting fixpoint interation In-Reply-To: <046.2b784c018fc4a62b657688676ee901f3@haskell.org> References: <046.2b784c018fc4a62b657688676ee901f3@haskell.org> Message-ID: <061.d7087ed7767bbca36169d54996ee92eb@haskell.org> #12368: Demand Analyzer: Cunnig plan not adhered to with aborting fixpoint interation -------------------------------------+------------------------------------- Reporter: nomeata | Owner: Type: bug | 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:D2392 Wiki Page: | -------------------------------------+------------------------------------- Comment (by nomeata): Working on this right now. I refactored the code quite a bit, removed some redundancies (such as passing around an strictness signature right next to an id, when that id is guaranteed to have been annotated with that strictness signature). Code pushed to `wip/12368`, push to Phabricator will happens once the automatic validators have validated the change. > I think there is no need to do addPessimisticSigs. Are you sure? Any variable with useful information (strict or used-once) will not be included in `lazy_fv` (according to `splitFVs`). If we now also remove them from the strictness signatures, their uses are not recorded anywhere – and then probably considered absent. I’ll try to produce a test case to verify that theory. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 21 15:09:57 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 21 Jul 2016 15:09:57 -0000 Subject: [GHC] #9718: Avoid TidyPgm predicting what CorePrep will do In-Reply-To: <046.5eef205a104808a079ad54238c650906@haskell.org> References: <046.5eef205a104808a079ad54238c650906@haskell.org> Message-ID: <061.b7cc72b06904a683c2186c8ebc4ef9d6@haskell.org> #9718: Avoid TidyPgm predicting what CorePrep will do -------------------------------------+------------------------------------- Reporter: simonpj | Owner: Type: task | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.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): really just a dup of #4121, but better explained here -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 21 15:50:36 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 21 Jul 2016 15:50:36 -0000 Subject: [GHC] #12368: Demand Analyzer: Cunnig plan not adhered to with aborting fixpoint interation In-Reply-To: <046.2b784c018fc4a62b657688676ee901f3@haskell.org> References: <046.2b784c018fc4a62b657688676ee901f3@haskell.org> Message-ID: <061.9bcd8029eb0408c3f03006a3850118fc@haskell.org> #12368: Demand Analyzer: Cunnig plan not adhered to with aborting fixpoint interation -------------------------------------+------------------------------------- Reporter: nomeata | Owner: Type: bug | 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:D2392 Wiki Page: | -------------------------------------+------------------------------------- Comment (by nomeata): > I’ll try to produce a test case to verify that theory. I have one that shows the problem. I could not reproduce it in the previous code where the (unsound, as shown in the test case above) strictness signatures were used, and these then included the demand on the strict free variables. Anyways, I need to run now. I have updated Phab:D2392 with my current code, for easier review. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 21 16:10:33 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 21 Jul 2016 16:10:33 -0000 Subject: [GHC] #12415: Fancy BinIface encoding for tuples is broken for constraint tuples In-Reply-To: <046.36b5b84566124dc8ed2f6851c925d504@haskell.org> References: <046.36b5b84566124dc8ed2f6851c925d504@haskell.org> Message-ID: <061.09cdd5b821925c42c52f5acca15ac4b5@haskell.org> #12415: Fancy BinIface encoding for tuples is broken for constraint tuples -------------------------------------+------------------------------------- Reporter: bgamari | Owner: 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: #12357 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): One of the roadblocks standing in the way of reinstating this encoding is that the constraint tuple's `Name`s are actually quite different from the other tuples (and even boxed/unboxed sums). There are five `Name`s associated with a type (or class) that we need to worry about in these cases, a. the `Name` of the `TyCon` b. the `Name` of its `DataCon` c. the `Name` of its `DataCon` worker d. the `Name` of its type representation e. the `Name` of its promoted data constructor type representation In the case of boxed and unboxed tuples a, b, and c are wired-in and d and e are known-key. In the case of constraint tuples, however, a is known-key and the rest are unknown to the compiler, requiring a lookup in the `GHC.Classes` interface file. This means that it is quite difficult to spot most of the `Name`s that for boxed and unboxed tuples we encode specially. Simon, do you think this is worth fixing? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 21 18:21:03 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 21 Jul 2016 18:21:03 -0000 Subject: [GHC] #12418: Make `MonadCont (ContT r m)` polykinded (r::k), (m::k -> Type) Message-ID: <051.aa98db01c615f5738620e369aa22a8a6@haskell.org> #12418: Make `MonadCont (ContT r m)` polykinded (r::k), (m::k -> Type) -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: feature | Status: new request | Priority: normal | Milestone: Component: Core | Version: 8.0.1 Libraries | 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: -------------------------------------+------------------------------------- == Issue == The current `MonadCont (ContT r m)` instance seems to have `r::Type` and `m::Type -> Type`. While this is accepted {{{ >>> :t callCC :: ((a -> ContT r m b) -> ContT r m a) -> ContT r m a callCC :: ((a -> ContT r m b) -> ContT r m a) -> ContT r m a :: ((a -> ContT r m b) -> ContT r m a) -> ContT r m a }}} this gets rejected {{{ >>> :set -XPolyKinds >>> :t callCC :: ((a -> ContT r m b) -> ContT r m a) -> ContT r m a :1:1: error: • No instance for (MonadCont (ContT r1 m1)) arising from a use of ‘callCC’ • In the expression: callCC :: ((a -> ContT r m b) -> ContT r m a) -> ContT r m a }}} and this doesn't reduce {{{ >>> :t callCC @(ContT _ _) callCC @(ContT _ _) :: MonadCont (ContT t t1) => ((a -> ContT t t1 b) -> ContT t t1 a) -> ContT t t1 a }}} the kinds must be specified {{{ >>> :t callCC @(ContT (_::Type) _) callCC @(ContT (_::Type) _) :: ((a -> ContT t t1 b) -> ContT t t1 a) -> ContT t t1 a }}} == Solution == This is unfortunate since since `callCC` can be kind polymorphic: {{{#!hs newtype ContT' r m a = ContT' { runContT' :: (a -> m r) -> m r } callCC' :: forall k a (r :: k) (m :: k -> Type) b. ((a -> ContT' r m b) -> ContT' r m a) -> ContT' r m a callCC' f = ContT' $ \ c -> runContT' (f (\ x -> ContT' $ \ _ -> c x)) c instance forall k (r::k) (m::k -> Type). MonadCont (ContT' r m) where callCC = callCC' }}} this works now {{{ >>> :t callCC @(ContT' _ _) callCC @(ContT' _ _) :: forall k (t :: k) (t1 :: k -> *) a b. ((a -> ContT' t t1 b) -> ContT' t t1 a) -> ContT' t t1 a }}} {{{ >>> :t callCC :: ((a -> ContT' r m b) -> ContT' r m a) -> ContT' r m a callCC :: ((a -> ContT' r m b) -> ContT' r m a) -> ContT' r m a :: forall k a (r :: k) (m :: k -> *) b. ((a -> ContT' r m b) -> ContT' r m a) -> ContT' r m a }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 21 18:36:49 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 21 Jul 2016 18:36:49 -0000 Subject: [GHC] #12419: Scheduling bug with forkOS + MVar Message-ID: <050.3157bd68c480bed634d3591e7003b69b@haskell.org> #12419: Scheduling bug with forkOS + MVar -----------------------------------------+--------------------------------- Reporter: luisgabriel | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Runtime System | Version: 8.0.1 Keywords: forkOS; scheduler | 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 have noticed a weird scheduling behavior when performing some experiments with the '''fasta''' benchmark [1] from The Computer Language Benchmarks Game. When I switch `forkIO` by `forkOS` the scheduler stops to assign work for some capabilities, and they stay idle for the whole execution of the program. ThreadScope view using forkIO: https://s31.postimg.org/r3mclspe3/fork_IO_N8_ghc8.png ThreadScope view using forkOS: https://s31.postimg.org/p9n265fff/fork_OS_N8_ghc8.png I was able to reproduce this behavior in both '''GHC 7.10.2''' and '''GHC 8.0.2'''. I was also able to reproduce it on two different machines running Ubuntu Server 14.04.3 LTS (kernel 3.19.0-25): - 2x10-core Intel Xeon E5-2660 v2 processors (Ivy Bridge), 2.20 GHz, with 256GB of DDR 1600MHz - 4-core Intel i7-3770 (IvyBridge) with 8 GB of DDR 1600MHz Source code + .eventlog files: https://dl.dropboxusercontent.com/u/5798150 /fasta-bug.zip [1] http://benchmarksgame.alioth.debian.org/u64q/program.php?test=fasta&lang=ghc&id=7 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 21 18:39:19 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 21 Jul 2016 18:39:19 -0000 Subject: [GHC] #12419: Scheduling bug with forkOS + MVar In-Reply-To: <050.3157bd68c480bed634d3591e7003b69b@haskell.org> References: <050.3157bd68c480bed634d3591e7003b69b@haskell.org> Message-ID: <065.b8732394cf744e72837c1249f57426bd@haskell.org> #12419: Scheduling bug with forkOS + MVar -------------------------------------+------------------------------------- Reporter: luisgabriel | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Runtime System | Version: 8.0.1 Resolution: | Keywords: forkOS; | scheduler 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 luisgabriel): * Attachment "forkIO-N8-ghc8.png" added. ThreadScope view using forkIO -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 21 18:40:52 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 21 Jul 2016 18:40:52 -0000 Subject: [GHC] #12419: Scheduling bug with forkOS + MVar In-Reply-To: <050.3157bd68c480bed634d3591e7003b69b@haskell.org> References: <050.3157bd68c480bed634d3591e7003b69b@haskell.org> Message-ID: <065.9609c0c243807de26befb4a9a918a91d@haskell.org> #12419: Scheduling bug with forkOS + MVar -------------------------------------+------------------------------------- Reporter: luisgabriel | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Runtime System | Version: 8.0.1 Resolution: | Keywords: forkOS; | scheduler 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 luisgabriel): * Attachment "forkOS-N8-ghc8.png" added. ThreadScope view using forkOS -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 21 19:32:52 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 21 Jul 2016 19:32:52 -0000 Subject: [GHC] #12420: Users guide link for hsc2hs has bitrotten Message-ID: <045.2ba362e1b9578cb50ac2c29c5bb4b687@haskell.org> #12420: Users guide link for hsc2hs has bitrotten -------------------------------------+------------------------------------- Reporter: ezyang | Owner: Type: task | Status: new Priority: normal | Milestone: Component: hsc2hs | 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: -------------------------------------+------------------------------------- https://hackage.haskell.org/package/hsc2hs links to http://www.haskell.org/ghc/docs/latest/html/users_guide/hsc2hs.html which is dead. I think https://downloads.haskell.org/~ghc/latest/docs/html/users_guide/utils.html #writing-haskell-interfaces-to-c-code-hsc2hs is what is desired. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 21 23:31:06 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 21 Jul 2016 23:31:06 -0000 Subject: [GHC] #12415: Fancy BinIface encoding for tuples is broken for constraint tuples In-Reply-To: <046.36b5b84566124dc8ed2f6851c925d504@haskell.org> References: <046.36b5b84566124dc8ed2f6851c925d504@haskell.org> Message-ID: <061.65fcc9b0f99a67b2f4d30bb84dbfde86@haskell.org> #12415: Fancy BinIface encoding for tuples is broken for constraint tuples -------------------------------------+------------------------------------- Reporter: bgamari | Owner: 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: #12357 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): Earlier today it occurred to me that `putName` already does a finite map lookup which made me think twice about the approach I took in #12357, {{{#!hs knownKeyNamesMap :: UniqFM Name knownKeyNamesMap = listToUFM_Directly [(nameUnique n, n) | n <- knownKeyNames] putName :: BinDictionary -> BinSymbolTable -> BinHandle -> Name -> IO () putName _dict BinSymbolTable{...} bh name | name `elemUFM` knownKeyNamesMap , let (c, u) = unpkUnique (nameUnique name) -- INVARIANT: (ord c) fits in 8 bits = ... }}} `knownKeyNamesMap` is currently used for two things, * A membership check is made when encoding a name in `putName` so we know that the `Name` can be encoded as just its unique. * A lookup is done in `getSymtabName` to recover the `Name` from the unique during deserialization The fact that we already do a lookup here puts an option for resolving this issue (as well as the tuple type representation issue of #12357) back on the table which I had previously ruled out in ticket:12357#comment:29. The idea is that we simply keep a lookup data structure containing `Name`s of things that need special treatment during interface file serialization. Indeed this is precisely what `knownKeyNamesMap` is. One option here would be to add the `Name`s of constraint tuples to this map and change it's type a bit, {{{#!hs data KnownKeyThing = -- | Tuple things get a fancy encoding of their own. -- While tuple type and data constructors are wired-in and therefore -- easy to spot, type reps are merely known key so we need to identify -- them by a look-up in 'knownKeyThingsMap'. TupleTypeRep !TupleSort !Arity -- | Constraint tuples. Only the 'TyCon's of these are known key. | CTupleTyCon !Arity -- | Boxed and unboxed sums (these have a similar encoding to tuples) | SumTyCon !Boxity !Arity | SumDataCon !Boxity !Arity !ConTagZ -- | Something which we know the key of; these things -- we encode in the interface file as just their 'Unique' | KnownKeyName Name knownKeyThingsMap :: NameEnv KnownKeyThing knownKeyThingsMap = mkNameEnv $ known_key_things ++ tuple_typerep_things ++ ctuple_things where known_key_things = [ (name, KnownKeyName name) | names <- knownKeyNames ] ctuple_things = [ (cTupleTyConName arity, CTupleTyCon arity) | arity <- [2..mAX_TUPLE_SIZE] ] tuple_typerep_things = [ (rep_name, TupleTypeRep tup_sort arity) | tup_sort <- [BoxedTuple, UnboxedTuple] , arity <- [2..mAX_TUPLE_SIZE] , let Just rep_name = tyConRepName_maybe $ tupleTyCon boxity arity ] }}} We'd then just modify the logic in `putName` to do the appropriate thing with the result of the lookup from this map. The deserialization side of things should be similarly straightforward (decoding the encoded `KnownKeyThing` and then doing what is necessary to turn it into a `Name`). -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 22 01:45:11 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 22 Jul 2016 01:45:11 -0000 Subject: [GHC] #12421: TestEquality and TestCoercion documentation is confusing Message-ID: <045.c655c505ffcb7aac601fde4e2ee18aac@haskell.org> #12421: TestEquality and TestCoercion documentation is confusing -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: Type: bug | Status: new Priority: normal | Milestone: 8.0.2 Component: Core | Version: 8.0.1 Libraries | 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: -------------------------------------+------------------------------------- Currently, the documentation for the `TestEquality` class indicates > This class contains types where you can learn the equality of two types from information contained in terms. Typically, only singleton types should inhabit this class. The `TestCoercion` documentation includes a similar caution about singleton types. But this is far too conservative! Length-indexed vectors can be made valid instances of `TestEquality` and `TestCoercion` in exactly one way: {{{#!hs data Nat = Z | S Nat data Vec a n where Nil :: Vec a 'Z Cons :: a -> Vec a n -> Vec a ('S n) instance TestEquality (Vec a) where testEquality Nil Nil = Just Refl testEquality (Cons _ xs) (Cons _ ys) = fmap (\Refl -> Refl) (testEquality xs ys) testEquality _ _ = Nothing instance TestCoercion (Vec a) where testCoercion xs ys = fmap (\Refl -> Coercion) (testEquality xs ys) }}} Polykinded heterogeneous lists are another nice non-singleton example for which each class has a single "most reasonable" instance: {{{#!hs data HList (f :: k -> *) (xs :: [k]) where HNil :: HList f '[] HCons :: f a -> HList f as -> HList f (a ': as) instance TestEquality f => TestEquality (HList f) where testEquality HNil HNil = Just Refl testEquality (HCons x xs) (HCons y ys) = do Refl <- testEquality x y Refl <- testEquality xs ys Just Refl testEquality _ _ = Nothing instance TestCoercion f => TestCoercion (HList f) where testCoercion HNil HNil = Just Coercion testCoercion (HCons x xs) (HCons y ys) = do Coercion <- testCoercion x y Coercion <- testCoercion xs ys Just Coercion testCoercion _ _ = Nothing }}} I don't know just how far the warning should be weakened; it may make sense to go as far as saying the type should generally be a GADT. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 22 02:23:14 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 22 Jul 2016 02:23:14 -0000 Subject: [GHC] #12422: Add decidable equality class Message-ID: <045.cc846fa4626d50a4033ca66a47264374@haskell.org> #12422: Add decidable equality class -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: Type: feature | Status: new request | Priority: normal | Milestone: Component: Core | Version: 8.0.1 Libraries | 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, we have a `TestEquality` class {{{#!hs class TestEquality f where testEquality :: f a -> f b -> Maybe (a :~: b) }}} It would be nice to add a class for fully decidable equality. There are a few options, but this one gets to the point rather quickly: {{{#!hs data EqDec a b where NotEqual :: (forall c . a :~: b -> c) -> EqDec a b Equal :: EqDec a a class DecEq f where decEq :: f a -> f b -> EqDec a b }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 22 02:48:35 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 22 Jul 2016 02:48:35 -0000 Subject: [GHC] #12418: Make `MonadCont (ContT r m)` polykinded (r::k), (m::k -> Type) In-Reply-To: <051.aa98db01c615f5738620e369aa22a8a6@haskell.org> References: <051.aa98db01c615f5738620e369aa22a8a6@haskell.org> Message-ID: <066.fcc915c688efb5ece611c1e849a95c04@haskell.org> #12418: Make `MonadCont (ContT r m)` polykinded (r::k), (m::k -> Type) -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: 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: | -------------------------------------+------------------------------------- Comment (by Iceland_jack): In the syntax of #12045 (which I hope to continue working on soon), a fully explicit instance might look like: {{{#!hs instance forall k (r::k) (m::k -> Type). MonadCont (ContT @k r m) where callCC :: ((a -> ContT @k r m b) -> ContT @k r m a) -> ContT @k r m a callCC = callCC' }}} and if we wanted the current version for some reason as defined in [https://hackage.haskell.org/package/mtl-2.2.1/docs/src/Control-Monad- Cont-Class.html Control.Monad.Cont.Class] (which doesn't seem to have `PolyKinds` enabled) {{{#!hs instance forall (r::Type) (m::Type -> Type). MonadCont (ContT @Type r m) where callCC :: ((a -> ContT @Type r m b) -> ContT @Type r m a) -> ContT @Type r m a callCC = callCC' }}} This could be displayed in `:info`, possibly given some flag or hiding given some smart heuristic. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 22 02:57:00 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 22 Jul 2016 02:57:00 -0000 Subject: [GHC] #12045: Visible kind application In-Reply-To: <051.f572b464c11770181720f8a1a7ec05a5@haskell.org> References: <051.f572b464c11770181720f8a1a7ec05a5@haskell.org> Message-ID: <066.c7a2d8736e961704fc42af151523ead0@haskell.org> #12045: Visible kind application -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Iceland_jack Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.1 Resolution: | Keywords: | TypeApplications TypeInType Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): ​Phab:D2216 Wiki Page: | -------------------------------------+------------------------------------- Comment (by Iceland_jack): Check comment:1:ticket:12418 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 22 08:09:39 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 22 Jul 2016 08:09:39 -0000 Subject: [GHC] #12423: Panic with DeriveAnyClass and DefaultSignatures Message-ID: <046.3f0136ae8585d6c3b1d74fb4b6476513@haskell.org> #12423: Panic with DeriveAnyClass and DefaultSignatures -------------------------------------+------------------------------------- Reporter: knrafto | Owner: 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: -------------------------------------+------------------------------------- With the code {{{#!hs {-# LANGUAGE DefaultSignatures, DeriveAnyClass #-} class Eq1 f where (==#) :: Eq a => f a -> f a -> Bool default (==#) :: Eq (f a) => f a -> f a -> Bool (==#) = (==) data Foo a = Foo (Either a a) deriving (Eq, Eq1) }}} GHC 8.0.1 and 7.10.3 both panic: {{{ ghc: panic! (the 'impossible' happened) (GHC version 8.0.1 for x86_64-apple-darwin): in other argument 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 Jul 22 09:02:28 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 22 Jul 2016 09:02:28 -0000 Subject: [GHC] #11469: GHCi should get LANGUAGE extensions/defaulting from the module whose full top-level scope is visible In-Reply-To: <045.1992743c6be5a313d344284f20ce0d35@haskell.org> References: <045.1992743c6be5a313d344284f20ce0d35@haskell.org> Message-ID: <060.dc47c33a4df815f4470e860f5fc273de@haskell.org> #11469: GHCi should get LANGUAGE extensions/defaulting from the module whose full top-level scope is visible -------------------------------------+------------------------------------- Reporter: ezyang | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: GHCi | Version: 7.11 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 thomie): See #12193 for a use case. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 22 09:05:19 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 22 Jul 2016 09:05:19 -0000 Subject: [GHC] #12393: Poor error message with equational type constraints In-Reply-To: <044.ac4c165f085adec9731a3cd7a651c47e@haskell.org> References: <044.ac4c165f085adec9731a3cd7a651c47e@haskell.org> Message-ID: <059.fe72324edc83aa59b99c4e2d0cc4adee@haskell.org> #12393: Poor error message with equational type constraints ---------------------------------+-------------------------------------- Reporter: laneb | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: GHCi | Version: 8.0.1 Resolution: invalid | Keywords: Operating System: Linux | Architecture: x86_64 (amd64) Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #11469 | Differential Rev(s): Wiki Page: | ---------------------------------+-------------------------------------- Changes (by thomie): * status: new => closed * component: Compiler => GHCi * resolution: => invalid * related: => #11469 Comment: If you turn on `GADTs` or `TypeFamilies` in GHCi, you'll get the error message you were hoping for. {{{ *Test> :set -XGADTs *Test> myFunc "z" :3:1: error: • Couldn't match expected type ‘Char’ with actual type ‘FooInner a0’ The type variable ‘a0’ is ambiguous • In the first argument of ‘print’, namely ‘it’ In a stmt of an interactive GHCi command: print it }}} I'm closing this ticket. I agree that the original error message is poor, but #11469 (the ticket referred to in comment:2) will fix the problem. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 22 12:37:32 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 22 Jul 2016 12:37:32 -0000 Subject: [GHC] #12368: Demand Analyzer: Cunnig plan not adhered to with aborting fixpoint interation In-Reply-To: <046.2b784c018fc4a62b657688676ee901f3@haskell.org> References: <046.2b784c018fc4a62b657688676ee901f3@haskell.org> Message-ID: <061.78c29e6303650f62e39e5c8c2c2fc184@haskell.org> #12368: Demand Analyzer: Cunnig plan not adhered to with aborting fixpoint interation -------------------------------------+------------------------------------- Reporter: nomeata | Owner: Type: bug | 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:D2392 Wiki Page: | -------------------------------------+------------------------------------- Comment (by nomeata): Fixed the problem, by adding a topDmd demand on all free variables mentioned in the strictness signature of the binders to `lazy_fvs`, before throwing away the strictness signature. Fixes this test case. Code on Phab and the branch, currently awaiting validation. While I am at it: `splitFVs` in `Demand.hs` has some intricate special handling for thunks, without any comment or justification. Do you have any idea why that is there, and whether it is still required? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 22 13:49:11 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 22 Jul 2016 13:49:11 -0000 Subject: [GHC] #12422: Add decidable equality class In-Reply-To: <045.cc846fa4626d50a4033ca66a47264374@haskell.org> References: <045.cc846fa4626d50a4033ca66a47264374@haskell.org> Message-ID: <060.141bab4981bd7f6139fdc20f53f449bb@haskell.org> #12422: Add decidable equality class -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: 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: | -------------------------------------+------------------------------------- Comment (by goldfire): Shouldn't this go via the libraries list? While what you have there works, I might prefer {{{#!hs type Refuted = a -> Void data Decision a = Yes a | No (Refuted a) class DecideEquality f where -- name lines up with TestEquality decideEquality :: f a -> f b -> Decision (a :~: b) }}} This solution does have one more level of indirection, but it allows you to extract an `a :~: b` from the `Decision`, which will compose better with the other functions from `Data.Type.Equality`. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 22 14:50:57 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 22 Jul 2016 14:50:57 -0000 Subject: [GHC] #12422: Add decidable equality class In-Reply-To: <045.cc846fa4626d50a4033ca66a47264374@haskell.org> References: <045.cc846fa4626d50a4033ca66a47264374@haskell.org> Message-ID: <060.16ce81a8972f96d3f5804364571a2a63@haskell.org> #12422: Add decidable equality class -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: 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: | -------------------------------------+------------------------------------- Comment (by Iceland_jack): Quick thought, is it possible to create a heterogeneous version of `TestEquality` that supports {{{#!hs eqTyCon :: forall (k1 k2 :: *). forall (a :: k1) (b :: k2). TTyCon a -> TTyCon b -> Maybe (a :~~: b) }}} Replacing `Maybe (a :~: b)` with `Maybe (a :~~: b)` would still constraint the kinds, would we need {{{#!hs class HTestEquality f1 f2 where htestEquality :: f1 a -> f2 b -> Maybe (a :~~: b) }}} ---- Discussed on `#ghc`, what would break if we made `:~:` heterogeneous? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 22 15:51:38 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 22 Jul 2016 15:51:38 -0000 Subject: [GHC] #12377: getExecutablePath doesn't return absolute path on OpenBSD (and maybe other OS also) In-Reply-To: <047.ce292d74547e5761ab80fddf4c2b76fa@haskell.org> References: <047.ce292d74547e5761ab80fddf4c2b76fa@haskell.org> Message-ID: <062.37c7eeeb54ebee697bb7f390153ee6b8@haskell.org> #12377: getExecutablePath doesn't return absolute path on OpenBSD (and maybe other OS also) -------------------------------------+------------------------------------- Reporter: oherrala | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: libraries/base | Version: 7.10.3 Resolution: | Keywords: Operating System: OpenBSD | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2423 Wiki Page: | -------------------------------------+------------------------------------- Changes (by oherrala): * differential: => Phab:D2423 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 22 16:04:21 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 22 Jul 2016 16:04:21 -0000 Subject: [GHC] #12422: Add decidable equality class In-Reply-To: <045.cc846fa4626d50a4033ca66a47264374@haskell.org> References: <045.cc846fa4626d50a4033ca66a47264374@haskell.org> Message-ID: <060.6b33a5704a6bc96a0d8c1a7a1a2df752@haskell.org> #12422: Add decidable equality class -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: 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: | -------------------------------------+------------------------------------- Comment (by goldfire): There are several fun things to respond to here! 1. Making `:~:` heterogeneous would likely break client code. The problem is that, right now, if I say `(Int :~: a)` somewhere, GHC can know that `a :: Type`. If we make `:~:` hetero, then GHC would rightly have `a :: k`, which can cause trouble. This is not hypothetical: I tried making this change once upon a time, and things broke. Even worse, it was hard to go from the error message reported to the actual cause. I advocate against this change. 2. We should have `:~~:` in the standard library. But I was too exhausted from implementing `TypeInType` to start this debate on the libraries mailing list. We should really put it in for 8.2. 3. Here is the hetero version of `TestEquality`: {{{ -- hetero class HTestEquality (f :: forall k. k -> Type) where hTestEquality :: f a -> f b -> Maybe (a :~~: b) }}} Note that `f` has to be polymorphic in its kind to avoid constraining `a` and `b` to have the same kind. Yes, this is a higher-rank kind! -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 22 17:00:51 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 22 Jul 2016 17:00:51 -0000 Subject: [GHC] #10957: getExecutablePath adds " (deleted)" suffix if executable was deleted under linux In-Reply-To: <047.9c6f417035b8e10ce588ba217f863194@haskell.org> References: <047.9c6f417035b8e10ce588ba217f863194@haskell.org> Message-ID: <062.5ac6ff488288f6fe214d824aa50804fd@haskell.org> #10957: getExecutablePath adds " (deleted)" suffix if executable was deleted under linux -------------------------------------+------------------------------------- Reporter: aslpavel | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Core Libraries | Version: 7.10.2 Resolution: | Keywords: Operating System: Linux | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by oherrala): * cc: oherrala (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 22 19:11:30 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 22 Jul 2016 19:11:30 -0000 Subject: [GHC] #12422: Add decidable equality class In-Reply-To: <045.cc846fa4626d50a4033ca66a47264374@haskell.org> References: <045.cc846fa4626d50a4033ca66a47264374@haskell.org> Message-ID: <060.fab24b92759b12db186cef881f9065b9@haskell.org> #12422: Add decidable equality class -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: 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: | -------------------------------------+------------------------------------- Comment (by Iceland_jack): Replying to [comment:3 goldfire]: > Yes, this is a higher-rank kind! Yikes! :) > 1. Making `:~:` heterogeneous would likely break client code. Figured as much. Is there any way to combine visible kind application (#12045) and unifying different type applications (#11385), let's say if I want to write something like {{{#!hs -- (:~~:) :: forall k1 k2. k1 -> k2 -> Type type (:~:) = (:~~:) @k @k :: k -> k -> Type -- using your syntax (visible kind abstraction?) type (:~:) = \@k -> (:~~:) @k @k }}} > 2. We should have `:~~:` in the standard library. But I was too exhausted from implementing `TypeInType` to start this debate on the libraries mailing list. We should really put it in for 8.2. Should I add it to `Data.Type.Equality` on Phab? ---- Should we rewrite `Const :: Type -> k -> Type` to have the kind ...? {{{#!hs data Const :: Type -> forall k. k -> Type where Const :: { getConst :: a } -> Const a b }}} Is there any way to define an `HTestEquality (Const e)` instance? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 22 19:22:33 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 22 Jul 2016 19:22:33 -0000 Subject: [GHC] #12418: Make `MonadCont (ContT r m)` polykinded (r::k), (m::k -> Type) In-Reply-To: <051.aa98db01c615f5738620e369aa22a8a6@haskell.org> References: <051.aa98db01c615f5738620e369aa22a8a6@haskell.org> Message-ID: <066.cd78c1b9afeeeb3de23d7fdf8a29cb41@haskell.org> #12418: Make `MonadCont (ContT r m)` polykinded (r::k), (m::k -> Type) -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: 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: | -------------------------------------+------------------------------------- Comment (by Iceland_jack): Without the kind the error was also confusing {{{ • No instance for (MonadCont (ContT r1 m1)) arising from a use of ‘callCC’ • In the expression: callCC :: ((a -> ContT r m b) -> ContT r m a) -> ContT r m a }}} It took me a while to recognize it was a ''kind'' problem, the instance certainly seems to be there! {{{#!hs instance MonadCont (ContT r m) }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 22 19:35:38 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 22 Jul 2016 19:35:38 -0000 Subject: [GHC] #12371: Error message, room for improvement In-Reply-To: <051.4451bd27ef0d80311d9b31d3cc46b800@haskell.org> References: <051.4451bd27ef0d80311d9b31d3cc46b800@haskell.org> Message-ID: <066.ba45c29b846d2e072ec92766ddd87ee4@haskell.org> #12371: Error message, room for improvement -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: bug | Status: merge Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: | TypeApplications 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 Iceland_jack): I think so -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 22 22:16:43 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 22 Jul 2016 22:16:43 -0000 Subject: [GHC] #12424: RTS stats show wrong productivity. Message-ID: <048.dd6f8ee273b20f973d503ab841f85657@haskell.org> #12424: RTS stats show wrong productivity. --------------------------------------+--------------------------------- Reporter: vagarenko | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Runtime System | Version: 8.0.1 Keywords: | Operating System: Windows Architecture: x86_64 (amd64) | Type of failure: None/Unknown Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: --------------------------------------+--------------------------------- I have this report after runnig my program: {{{ INIT time 0.000s ( 0.001s elapsed) MUT time 29.344s ( 56.484s elapsed) GC time 4.306s ( 1.589s elapsed) EXIT time 0.000s ( 0.001s elapsed) Total time 33.649s ( 58.075s elapsed) Alloc rate 1,530,969,741 bytes per MUT second Productivity 87.2% of total user, 50.5% of total elapsed }}} Elapsed productivity is wrong. It should be `MUT elapsed / Total elapsed = 56.484 / 58.075 = 0.972` but it looks like `MUT user / Total elapsed = 29.344 / 58.075 = 0.505` Looks like the code at https://github.com/ghc/ghc/blob/a88bb1b1518389817583290acaebfd6454aa3cec/rts/Stats.c#L702-L704 uses wrong numerator for elapsed value. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 22 22:34:42 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 22 Jul 2016 22:34:42 -0000 Subject: [GHC] #12422: Add decidable equality class In-Reply-To: <045.cc846fa4626d50a4033ca66a47264374@haskell.org> References: <045.cc846fa4626d50a4033ca66a47264374@haskell.org> Message-ID: <060.3e3190107202d09a4918d16984cb4fe4@haskell.org> #12422: Add decidable equality class -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: 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: | -------------------------------------+------------------------------------- Comment (by goldfire): Replying to [comment:4 Iceland_jack]: > Figured as much. Is there any way to combine visible kind application (#12045) and unifying different type applications (#11385), let's say if I want to write something like > > {{{#!hs > -- (:~~:) :: forall k1 k2. k1 -> k2 -> Type > > type (:~:) = (:~~:) @k @k :: k -> k -> Type > > -- using your syntax (visible kind abstraction?) > type (:~:) = \@k -> (:~~:) @k @k > }}} This is an interesting thought. It can be done in today's syntax: {{{#!hs type (:~:) = ((:~~:) :: k -> k -> Type) pattern Refl :: () => (a ~ b) => a :~: b pattern Refl = HRefl }}} I wonder what the consequences are (if any) of reimplementing `:~:` and `Refl` this way. > > > 2. We should have `:~~:` in the standard library. But I was too exhausted from implementing `TypeInType` to start this debate on the libraries mailing list. We should really put it in for 8.2. > > Should I add it to `Data.Type.Equality` on Phab? This should be a proposal to the libraries mailing list first. What supporting functions will you have? Perhaps if we use the pattern synonym approach for `:~:` then many existing functions can be reused. I'd be quite pleased if you spearhead this! > > ---- > > Should we rewrite `Const :: Type -> k -> Type` to have the kind ...? > > {{{#!hs > data Const :: Type -> forall k. k -> Type where > Const :: { getConst :: a } -> Const a b > }}} Yes. This is slightly more general than quantifying over `k` at the top. > > Is there any way to define an `HTestEquality (Const e)` instance? No. Why would you think there is? `HTestEquality (Const e)` (with your new `Const`) is well-kinded, but I can't imagine an implementation for `hTestEquality`. In general, it's best to quantify over kinds as late as possible, because GHC can't reshuffle where the quantifications are like it can in terms. (When we get `-XDependentTypes`, this deficiency will be resolved.) It may not be worth the effort, but in theory, we should redefine datatypes to have kind quantifications as far to the right as possible. This includes the following preferred declaration for `:~~:`: {{{ data (:~~:) :: forall k1. k1 -> forall k2. k2 -> Type where HRefl :: a :~~: a }}} Sadly, then, there seems to be no way to define `:~:` in terms of `:~~:`. GHC just isn't smart enough to get the kind quantification to work. (Relatedly: kind quantification around type synonyms is very murky and not quite specified.) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 22 23:33:30 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 22 Jul 2016 23:33:30 -0000 Subject: [GHC] #12425: With -O1 and above causes ghc to use all available memory before being killed by OOM killer Message-ID: <044.8db07ee1e56d0d370ac594dbce3dff94@haskell.org> #12425: With -O1 and above causes ghc to use all available memory before being killed by OOM killer -------------------------------------+------------------------------------- Reporter: erikd | Owner: Type: bug | Status: new Priority: normal | Milestone: 8.0.2 Component: Compiler | Version: 8.0.1 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've just taken over an existing haskell package and in the process of getting it to work with ghc 8.0 discovered that when compiling one file ghc tires to use all my ram. It basically ends up using 40% of 16 Gig before being killed by the OOM (out-of-memory) killer. The project is at: https://github.com/erikd/conduit-find.git The problem can be reproduced by: {{{ git clone https://github.com/erikd/conduit-find.git cd conduit-find git checkout test/ghc-8.0 cabal sandbox init cabal install --dependencies-only cabal build }}} which on two of my machines fails building the `Data.Cond` module. This is regression, because this code compiles fine with ghc-7.10.3 and ghc-7.8.4. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 22 23:47:15 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 22 Jul 2016 23:47:15 -0000 Subject: [GHC] #12425: With -O1 and above causes ghc to use all available memory before being killed by OOM killer In-Reply-To: <044.8db07ee1e56d0d370ac594dbce3dff94@haskell.org> References: <044.8db07ee1e56d0d370ac594dbce3dff94@haskell.org> Message-ID: <059.5f0f466141cad3718bed0b0e45bed1f7@haskell.org> #12425: With -O1 and above causes ghc to use all available memory before being killed by OOM killer -------------------------------------+------------------------------------- Reporter: erikd | Owner: Type: bug | Status: new Priority: normal | Milestone: 8.0.2 Component: Compiler | Version: 8.0.1 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 erikd): @carter suggested that adding the `Safe` language pragma might prevent this, but it didn't help. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jul 23 00:35:36 2016 From: ghc-devs at haskell.org (GHC) Date: Sat, 23 Jul 2016 00:35:36 -0000 Subject: [GHC] #12418: Make `MonadCont (ContT r m)` polykinded (r::k), (m::k -> Type) In-Reply-To: <051.aa98db01c615f5738620e369aa22a8a6@haskell.org> References: <051.aa98db01c615f5738620e369aa22a8a6@haskell.org> Message-ID: <066.57dc2146a43c6995a601b67bc21b3b0d@haskell.org> #12418: Make `MonadCont (ContT r m)` polykinded (r::k), (m::k -> Type) -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: 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: | -------------------------------------+------------------------------------- Comment (by ekmett): I have some rather large concerns about the fact that now selecting the sensible existing monad transformer instances becomes quite brittle. {{{#!hs instance [safe] forall r (m :: Type -> Type). MonadCont (ContT @Type r m) }}} requires `k :: Type` to be figured out before it'll be selected. So you get the ability to define your own `callCC` and other operations where `(r :: MyKind)` and `(m :: MyKind -> *)` by making other instances pointwise at particular kinds, but now if you are polymorphic enough, you'll get "No instance" warnings that are completely opaque to the average user. The FlexibleInstance-style shape of the instance head here is a sign that inference will go to hell. If the instance was based on something like {{{#!hs instance k ~ Type => MonadCont (ContT @k r m) }}} then type inference for that particular instance could never blow up, at the expense of losing ability to co-opt callCC for some unrelated monad- transformer-like pipeline that worked on an entirely different kind that could never be made compatible with the way the rest of the MonadFoo classes lift over `m`, anyways. Attempting to use `callCC` with that sort of tweak would then force k = Type, and inference could proceed as usual. Of course even if we did do that, we just stuck one finger in the dyke. There are other leaks. e.g. What makes this instance any different than the behavior of `MonadState s` or `MonadReader e`? They all need `m :: Type -> Type`, so they'll _all_ have these inference woes, `Cont r m :: * -> *`, so they could be instances of `MonadState s` at any choice of kind k, but the lifting of `MonadState s` requires `m :: Type -> Type`, etc. So now attempting to call `get`, `ask`, etc. in a sufficiently polymorphic situation would run afoul of the same thing! It seems every one of those instances would need to adopt the same pattern. The fact that our behavior for any of the instances we use `ContT r m` at that exploit information about `m` is tied to m having kind `* -> *` makes this a mess, and that all the transformer instances become significantly harder to use makes me very nervous. User code that defines instances that lift over ContT won't exhibit the same care. The fact that the only thing we gain here seems to be the ability to define instances that relies on working pointwise completely differently at different kinds, and really tricky type errors for the kinds of users most ill equipped to handle them makes me think this probably isn't a good idea. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jul 23 02:20:42 2016 From: ghc-devs at haskell.org (GHC) Date: Sat, 23 Jul 2016 02:20:42 -0000 Subject: [GHC] #11646: Make pattern synonym export type mismatch a warning In-Reply-To: <045.9eb8b2d1f35f468ff5981bb2e5b0840b@haskell.org> References: <045.9eb8b2d1f35f468ff5981bb2e5b0840b@haskell.org> Message-ID: <060.1a8d56355270eaa4c496fe97020e1918@haskell.org> #11646: Make pattern synonym export type mismatch a warning -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: Type: feature request | Status: closed Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.1-rc2 checker) | Keywords: Resolution: wontfix | PatternSynonyms 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: | PatternSynonyms/AssociatingSynonyms| -------------------------------------+------------------------------------- Comment (by dfeuer): Replying to [comment:3 thomie]: > No response from submitter. Unclear which problem this feature would solve. Please reopen if you disagree. I disagree on philosophical grounds somewhat more than practical grounds. Pattern synonyms are fundamentally a ''syntactic'' feature. The essential idea is that we're writing introduction and elimination functions and tying them to construction and pattern matching syntax. In the associated pattern syntax, we tie a type constructor ''name'' to pattern synonym ''bindings''. The type checker has essentially nothing useful to contribute at the export stage. I think it should really stay completely out of the way. Others disagree, for their own reasons, but I'd like to at least be able to say that ''I'' don't care and I'd like it to leave me alone. I'll be opening another ticket shortly relating to a more practical problem with the way pattern synonyms are typed, to which the most obvious solution is essentially "Just let me do what I want, because it can't hurt type safety." Same philosophy here. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jul 23 02:20:59 2016 From: ghc-devs at haskell.org (GHC) Date: Sat, 23 Jul 2016 02:20:59 -0000 Subject: [GHC] #11646: Make pattern synonym export type mismatch a warning In-Reply-To: <045.9eb8b2d1f35f468ff5981bb2e5b0840b@haskell.org> References: <045.9eb8b2d1f35f468ff5981bb2e5b0840b@haskell.org> Message-ID: <060.30f5a9e065a0030cb3746946ec45a3bc@haskell.org> #11646: Make pattern synonym export type mismatch a warning -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.1-rc2 checker) | Keywords: Resolution: | PatternSynonyms 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: | PatternSynonyms/AssociatingSynonyms| -------------------------------------+------------------------------------- Changes (by dfeuer): * status: closed => new * resolution: wontfix => -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jul 23 02:34:51 2016 From: ghc-devs at haskell.org (GHC) Date: Sat, 23 Jul 2016 02:34:51 -0000 Subject: [GHC] #12426: Allow smart constructors their own types Message-ID: <045.935c148fda32feaf05d8d4eda84c7495@haskell.org> #12426: Allow smart constructors their own types -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: Type: feature | Status: new request | 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: -------------------------------------+------------------------------------- GHC currently offers one-way pattern synonyms allowing general deconstruction with nice syntax. And it offers bidirectional pattern synonyms, which toss in construction functions that start with capital letters. Unfortunately, it forces the construction and deconstruction sides to share a type. This is sometimes rather unfortunate. The documentation itself points out the limitation with regard to matching numeric literals (where deconstruction requires `Eq`). Another example is Edward Yang's `NF` type, whose smart constructor (but not deconstructor) requires `NFData`. I think the easiest fix is to allow a type signature in the `where` clause of a pattern synonym definition. {{{#!hs pattern X :: Eq a => a -> Foo pattern X q <- ... where X :: X a => a -> Foo X a = ... }}} Ideally, I'd like to offer the other one-way (constructor without pattern) as well, but I care less about that. }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jul 23 07:15:43 2016 From: ghc-devs at haskell.org (GHC) Date: Sat, 23 Jul 2016 07:15:43 -0000 Subject: [GHC] #12426: Allow smart constructors their own types In-Reply-To: <045.935c148fda32feaf05d8d4eda84c7495@haskell.org> References: <045.935c148fda32feaf05d8d4eda84c7495@haskell.org> Message-ID: <060.923676e6fc3d8a85c7e89576ee25516d@haskell.org> #12426: Allow smart constructors their own types -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: Type: feature request | Status: new Priority: normal | Milestone: 8.2.1 Component: Compiler | Version: 8.0.1 Resolution: | Keywords: | PatternSynonyms Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #8581 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by mpickering): * keywords: => PatternSynonyms * related: => #8581 Comment: This is essentially #8581. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jul 23 07:35:38 2016 From: ghc-devs at haskell.org (GHC) Date: Sat, 23 Jul 2016 07:35:38 -0000 Subject: [GHC] #12425: With -O1 and above causes ghc to use all available memory before being killed by OOM killer In-Reply-To: <044.8db07ee1e56d0d370ac594dbce3dff94@haskell.org> References: <044.8db07ee1e56d0d370ac594dbce3dff94@haskell.org> Message-ID: <059.feb32b0b2a405545e4e3d949ee6dd0d0@haskell.org> #12425: With -O1 and above causes ghc to use all available memory before being killed by OOM killer -------------------------------------+------------------------------------- Reporter: erikd | Owner: Type: bug | Status: new Priority: normal | Milestone: 8.0.2 Component: Compiler | Version: 8.0.1 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 erikd): Maybe not too surprisingly, removing all the `INLINE` pragmas (51 in 500 lines of code) allows the code to compile even with `-O2`. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jul 23 09:21:17 2016 From: ghc-devs at haskell.org (GHC) Date: Sat, 23 Jul 2016 09:21:17 -0000 Subject: [GHC] #12427: Type inference regression with RankNTypes (GHC 8.1) Message-ID: <045.c0f95031d5d84dce2d172c79ab762b36@haskell.org> #12427: Type inference regression with RankNTypes (GHC 8.1) -------------------------------------+------------------------------------- Reporter: thomie | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.1 (Type checker) | Keywords: 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): | Wiki Page: -------------------------------------+------------------------------------- The following module compiles fine with ghc-8.0.1: {{{#!hs {-# LANGUAGE RankNTypes #-} module Acquire where newtype Acquire a = Acquire {unAcquire :: (forall b. b -> b) -> IO a} instance Functor Acquire where fmap = undefined instance Applicative Acquire where pure = undefined (<*>) = undefined instance Monad Acquire where Acquire f >>= g' = Acquire $ \restore -> do x <- f restore let Acquire g = g' x -- let g = unAcquire (g' x) g restore }}} HEAD (83e4f49577665278fe08fbaafe2239553f3c448e, ghc-8.1.20160720) reports: {{{ Acquire.hs:17:21: error: • Couldn't match expected type ‘t’ with actual type ‘(forall b1. b1 -> b1) -> IO b’ ‘t’ is a rigid type variable bound by the inferred type of g :: t at Acquire.hs:17:13-28 • In the pattern: Acquire g In a pattern binding: Acquire g = g' x In the expression: do { x <- f restore; let Acquire g = g' x; g restore } • Relevant bindings include g' :: a -> Acquire b (bound at Acquire.hs:15:19) (>>=) :: Acquire a -> (a -> Acquire b) -> Acquire b (bound at Acquire.hs:15:15) }}} This example is reduced from the `recourcet` package on Hackage, module `Data.Acquire.Internal`. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jul 23 09:51:17 2016 From: ghc-devs at haskell.org (GHC) Date: Sat, 23 Jul 2016 09:51:17 -0000 Subject: [GHC] #12427: Type inference regression with RankNTypes (GHC 8.1) In-Reply-To: <045.c0f95031d5d84dce2d172c79ab762b36@haskell.org> References: <045.c0f95031d5d84dce2d172c79ab762b36@haskell.org> Message-ID: <060.d564e1259a7aeede97c463a479657fea@haskell.org> #12427: Type inference regression with RankNTypes (GHC 8.1) -------------------------------------+------------------------------------- Reporter: thomie | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.1 checker) | Resolution: | Keywords: 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): Wiki Page: | -------------------------------------+------------------------------------- Changes (by erikd): * cc: erikd (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jul 23 13:51:03 2016 From: ghc-devs at haskell.org (GHC) Date: Sat, 23 Jul 2016 13:51:03 -0000 Subject: [GHC] #12425: With -O1 and above causes ghc to use all available memory before being killed by OOM killer In-Reply-To: <044.8db07ee1e56d0d370ac594dbce3dff94@haskell.org> References: <044.8db07ee1e56d0d370ac594dbce3dff94@haskell.org> Message-ID: <059.279931c14cce90af49ce52d7c514782f@haskell.org> #12425: With -O1 and above causes ghc to use all available memory before being killed by OOM killer -------------------------------------+------------------------------------- Reporter: erikd | Owner: Type: bug | Status: new Priority: high | Milestone: 8.0.2 Component: Compiler | Version: 8.0.1 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 thomie): * priority: normal => high Comment: Reproducible with HEAD. Here is a testcase that doesn't depend on any packages that aren't in the GHC tree. {{{#!hs module T12425 where import Control.Applicative import Control.Monad import Control.Monad.Trans.State.Lazy (StateT(..)) data Result a m b = RecurseOnly (Maybe (CondT a m b)) | KeepAndRecurse b (Maybe (CondT a m b)) instance Monad m => Functor (Result a m) where fmap f (RecurseOnly l) = RecurseOnly (liftM (fmap f) l) fmap f (KeepAndRecurse a l) = KeepAndRecurse (f a) (liftM (fmap f) l) {-# INLINE fmap #-} newtype CondT a m b = CondT { getCondT :: StateT a m (Result a m b) } instance Monad m => Functor (CondT a m) where fmap f (CondT g) = CondT (liftM (fmap f) g) {-# INLINE fmap #-} instance Monad m => Applicative (CondT a m) where pure = undefined (<*>) = undefined instance Monad m => Monad (CondT a m) where return = undefined (>>=) = undefined }}} @erikd: the following change fixes the problem. {{{#!hs instance Monad m => Functor (CondT a m) where - fmap f (CondT g) = CondT (liftM (fmap f) g) + fmap f (CondT g) = CondT (liftA (fmap f) g) {-# INLINE fmap #-} }}} Tested with GHC 8 and HEAD. To compile `conduit-find` with HEAD, you need to make the following other changes: * add `Cabal < 1.25` to the .cabal file, to workaround https://github.com/ekmett/distributive/issues/17 * use `conduit` with this patch: https://github.com/snoyberg/conduit/pull/274 * use `tagged` >= 0.8.5, which fixes https://github.com/ekmett/semigroupoids/issues/48 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jul 23 13:54:25 2016 From: ghc-devs at haskell.org (GHC) Date: Sat, 23 Jul 2016 13:54:25 -0000 Subject: [GHC] #8581: Pattern synonym used in an expression context could have different constraints to pattern used in a pattern context In-Reply-To: <045.ffb8b433d262c0e3b5b415c2eeca2eee@haskell.org> References: <045.ffb8b433d262c0e3b5b415c2eeca2eee@haskell.org> Message-ID: <060.3b53239c3d90614fb0eb0da53147322f@haskell.org> #8581: Pattern synonym used in an expression context could have different constraints to pattern used in a pattern context -------------------------------------+------------------------------------- Reporter: cactus | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 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 dfeuer): Replying to [comment:34 simonpj]: > Let's not think about implementation before we have a ''design''. I have not read the entire thread again, but I'm pretty convinced that > > * We can't have two different types, one for construction and one for pattern matching > > I think it'll just be too confusing to have two types. It's bad enough to have this provided/required stuff without, in addition, having a completely separate type for construction. Are you seriously proposing to have two signatures for each pattern synonym? (Optionally, I assume.) I respectfully disagree. Pattern synonyms are not, and likely will never be, written by many beginners. And very few programmers are likely to need to write terribly many of them. I think, therefore, that making the type checker enforce some sort of "reasonableness" on them is a considerably lower priority than making them powerful enough to do what librarians need them to do. I ran into this yesterday writing a pattern synonym for Edward Yang's `NF` type (in the `nf` package), which needs a constraint on construction but not on matching. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jul 23 17:45:11 2016 From: ghc-devs at haskell.org (GHC) Date: Sat, 23 Jul 2016 17:45:11 -0000 Subject: [GHC] #12428: Allow pattern synonyms to optionally carry coerceability Message-ID: <045.f7b089d2570bb063442b06cde2fff958@haskell.org> #12428: Allow pattern synonyms to optionally carry coerceability -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: Type: feature | Status: new request | 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: -------------------------------------+------------------------------------- Aside from their more interesting abilities, pattern synonyms can be used for name management. For example, if a module exports a type with a data constructor named `A`, and also re-exports a type with a data constructor named `A`, it can use a pattern synonym to rename the imported constructor. If the type is a `newtype`, this pattern synonym will not carry coerceability. Sometimes, this is exactly what one would desire (an "unsafe" module breaking through a newtype abstraction may wish to allow importers to confine coerceability). Other times, it's not (pattern synonym just for name control). When defining a pattern synonym for a type in a module in which that type is coerceable, it would be nice to be able to tell GHC that the pattern synonym should carry coerceability. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jul 23 17:52:15 2016 From: ghc-devs at haskell.org (GHC) Date: Sat, 23 Jul 2016 17:52:15 -0000 Subject: [GHC] #12422: Add decidable equality class In-Reply-To: <045.cc846fa4626d50a4033ca66a47264374@haskell.org> References: <045.cc846fa4626d50a4033ca66a47264374@haskell.org> Message-ID: <060.b1e3fa993f5c615a8c7b23fcf21ce8fd@haskell.org> #12422: Add decidable equality class -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: 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: | -------------------------------------+------------------------------------- Comment (by Iceland_jack): Replying to [comment:5 goldfire]: > This should be a proposal to the libraries mailing list first. What supporting functions will you have? Perhaps if we use the pattern synonym approach for `:~:` then many existing functions can be reused. I'd be quite pleased if you spearhead this! > I wonder what the consequences are (if any) of reimplementing `:~:` and `Refl` this way. I've tried it with every occurrence of `:~:` in base and it seems to work fine, quite a few functions became more general as a result. The change means `show Refl == show HRefl` (unless we use some type class magic) and {{{#!hs instance a ~~ b => Read ((a::k1) :~~: (b::k2)) where readsPrec d = readParen (d > 10) (\r -> [(HRefl, s) | ("HRefl",s) <- lex r ]) instance a ~~ b => Enum ((a::k1) :~~: (b::k2)) instance a ~~ b => Bounded ((a::k1) :~~: (b::k2)) }}} One downside: You may intend to use heterogeneous equality with `HRefl` but something else unifies the kinds without your knowledge. ---- Does it make sense for `Coercible` / `Coercion` to be heterogeneous? {{{#!hs repr :: forall k1 k2 (a::k1) (b::k2). a :~~: b -> Coercion a b }}} ---- Some weirdness about ordering of kind variables: {{{#!hs data (a::k1) :~~: (b::k2) where HRefl :: a :~~: a -- instance forall k2 k1 (a :: k1) (b :: k2). Show (a :~~: b) deriving instance Show (a :~~: b) }}} `k2` appears before `k1`, I can't remember if this was fixed but this gives you the right order `Show ((a::k1) :~~: (b::k2))`. ---- Given {{{#!hs import GHC.Types data (a::k1) :~~: (b::k2) where HRefl :: a :~~: a pattern Refl :: () => (a ~ b) => (a::k) :~: (b::k) pattern Refl = HRefl type (:~:) = ((:~~:) :: k -> k -> Type) }}} Why does this work?? Shouldn't `Refl` constrain the kinds? {{{#!hs -- instance forall k1 k2 (a :: k1) (b :: k2). (a :: k1) ~~ (b :: k2) => Bounded (a :~~: b) instance a ~~ b => Bounded ((a::k1) :~~: (b::k2)) where minBound = Refl maxBound = Refl }}} ---- > No. Why would you think there is? Actually with the [https://github.com/koengit/KeyMonad/blob/master/paper.lhs Key monad] I was able to write an implementation. I'll post it in a follow up reply. > Sadly, then, there seems to be no way to define `:~:` in terms of `:~~:`. GHC just isn't smart enough to get the kind quantification to work. (Relatedly: kind quantification around type synonyms is very murky and not quite specified.) I assume `:~:` in terms of `(:~~:) :: forall k1. k1 -> forall k2. k2 -> Type`. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jul 23 18:27:58 2016 From: ghc-devs at haskell.org (GHC) Date: Sat, 23 Jul 2016 18:27:58 -0000 Subject: [GHC] #12422: Add decidable equality class In-Reply-To: <045.cc846fa4626d50a4033ca66a47264374@haskell.org> References: <045.cc846fa4626d50a4033ca66a47264374@haskell.org> Message-ID: <060.3fdb8de9c6db920107d7202b25a125dc@haskell.org> #12422: Add decidable equality class -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: 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: | -------------------------------------+------------------------------------- Comment (by Iceland_jack): This is what I missed from the paper: > The `base` library `Data.Typeable` provides similar functionality to the Key monad. Typeable is a type class that provides a value-level representation of the types that implement it. The `Typeable` library provides a function > > {{{#!hs > eqT :: forall a b. (Typeable a, Typeable b) => Maybe (a :~: b) > }}} > > where `(:~:)` is the GADT from Figure .... This function gives `Just Refl` if both ''types'' are the same, whereas `testEquality` from the Key monad only gives `Just Refl` if the ''keys'' are the same. If we have two keys with the same type, but which originate from different `newKey` invocations, the result of `testEquality` will be `Nothing`. My initial thought was ‘if we only had `Typeable` constraints’: {{{#!hs class HTestEquality (f :: forall k. k -> Type) where hTestEquality :: (Typeable a, Typeable b) => f a -> f b -> Maybe (a :~~: b) instance HTestEquality (Const' e) where hTestEquality :: forall a b. (Typeable a, Typeable b) => Const' e a -> Const' e b -> Maybe (a :~~: b) hTestEquality Const'{} Const'{} = heqT @a @b heqT :: forall a b. (Typeable a, Typeable b) => Maybe (a :~~: b) heqT = do guard (typeRep (Proxy :: Proxy a) == typeRep (Proxy :: Proxy b)) pure (unsafeCoerce HRefl) }}} But then I remembered this line from the Key monad paper: > This gives us a form of dynamic typing, ''without'' the need for `Typeable` constraints. [https://github.com/koengit/KeyMonad/blob/master/KeyM.hs KeyM] with some modifications {{{#!hs -- data Key s a = Key Name data Key :: forall k1. k1 -> forall k2. k2 -> Type where Key :: Name -> Key s a }}} and define {{{#!hs class HTestEquality (f :: forall k. k -> Type) where hTestEquality :: f a -> f b -> Maybe (a :~~: b) instance HTestEquality (Key s) where hTestEquality :: Key s a -> Key s b -> Maybe (a :~~: b) hTestEquality (Key i) (Key j) = do guard (i == j) pure (unsafeCoerce HRefl) instance HTestEquality (Const' e) where hTestEquality :: forall a b. Const' e a -> Const' e b -> Maybe (a :~~: b) hTestEquality Const'{} Const'{} = runKeyM $ do a_key <- newKey @a b_key <- newKey @b pure (a_key =?= b_key) }}} But `a_key` and `b_key` come from different `newKey` invocations, so they will always equal `Nothing`... oh well. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jul 23 18:30:13 2016 From: ghc-devs at haskell.org (GHC) Date: Sat, 23 Jul 2016 18:30:13 -0000 Subject: [GHC] #8581: Pattern synonym used in an expression context could have different constraints to pattern used in a pattern context In-Reply-To: <045.ffb8b433d262c0e3b5b415c2eeca2eee@haskell.org> References: <045.ffb8b433d262c0e3b5b415c2eeca2eee@haskell.org> Message-ID: <060.db9b92b56e1135736e9ace41b2e012d3@haskell.org> #8581: Pattern synonym used in an expression context could have different constraints to pattern used in a pattern context -------------------------------------+------------------------------------- Reporter: cactus | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 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 goldfire): While we're at this, there is another outstanding issue: a pattern synonym type should give some indication of the synonym's directionality. I think there are two quite separable questions here: 1. What features do we want GHC to support? 2. What concrete syntax will support those features? Let's tackle these design questions in order. For (1) the fundamental question seems to be: 1a. What relationship between the expression-type and the pattern-type do we wish to require? Possible answers: A. None at all. B. The types have the same structure, but perhaps different constraints. C. Something in between. For example, both have to have the same arity and/or the same head of the result type. Personally, I think only A or B is defensible here. Furthermore, I favor A. History has shown that Haskellers like as much freedom to explore as possible. There is no type safety issue at hand. So let's give people more rope. I wager the idea of one symbol having two different types (in two very-easy-to-distinguish contexts) is less confusing than, say, kind polymorphism. Now, onto design point (2). I wonder if it's helpful to think of pattern synonym types as a `(PatternType, Maybe Type)`. The first component is a pattern-type, with its separate provided and required contexts, etc. It classifies the pattern synonym when used as a pattern. The second component is (perhaps) the type of the pattern synonym when used as an expression. This component is missing, naturally, when the synonym is unidirectional. Note that this component (when it exists) is just a normal type. Typically, the second component can be constructed in a straightforward manner from the first (if the synonym is bidirectional). But it need not be. Thinking along these lines, I propose the following rules for syntax: 1. `pattern :: `, when written outside of a `-boot` file, sets the first component of the type. It also sets the second component of the type when there is no separate type signature for `` and when the pattern is declared to be bidirectional. 2. ` :: Type` can be written to set the second component of a pattern synonym type. 3. In a `-boot` file, a `pattern :: ` sets only the first component of a pattern synonym type. If you want a bidirectional pattern synonym, write two signatures. Note that point (2) creates something like a top-level signature (the kind we use all the time when defining functions) but for a capitalized (or `:`-prefixed) identifier. As far as I can tell, this is a new spot in the grammar (ignoring "naked" top-level declaration splices that consist of one identifier followed by a type annotation, which conflict with normal type signatures, anyway). What do we think? Please consider addressing design point (1) separately from design point (2), as I think that will simplify the discussion. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jul 23 18:39:18 2016 From: ghc-devs at haskell.org (GHC) Date: Sat, 23 Jul 2016 18:39:18 -0000 Subject: [GHC] #8581: Pattern synonym used in an expression context could have different constraints to pattern used in a pattern context In-Reply-To: <045.ffb8b433d262c0e3b5b415c2eeca2eee@haskell.org> References: <045.ffb8b433d262c0e3b5b415c2eeca2eee@haskell.org> Message-ID: <060.43dee77f81f9fbe8ccec689d26ee6c9b@haskell.org> #8581: Pattern synonym used in an expression context could have different constraints to pattern used in a pattern context -------------------------------------+------------------------------------- Reporter: cactus | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 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 dfeuer): Replying to [comment:38 goldfire]: > A. None at all. I'm very much in favor of A. See also #11646. > Now, onto design point (2). I wonder if it's helpful to think of pattern synonym types as a `(PatternType, Maybe Type)`. I think what we actually want (borrowing from the [https://hackage.haskell.org/package/these these] package) is `These PatternType Type`. That is, either just the pattern, just the constructor, or both. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jul 23 20:23:35 2016 From: ghc-devs at haskell.org (GHC) Date: Sat, 23 Jul 2016 20:23:35 -0000 Subject: [GHC] #12418: Make `MonadCont (ContT r m)` polykinded (r::k), (m::k -> Type) In-Reply-To: <051.aa98db01c615f5738620e369aa22a8a6@haskell.org> References: <051.aa98db01c615f5738620e369aa22a8a6@haskell.org> Message-ID: <066.03b4576e228a0d7f605ae3fa14e9b324@haskell.org> #12418: Make `MonadCont (ContT r m)` polykinded (r::k), (m::k -> Type) -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: 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: | -------------------------------------+------------------------------------- Comment (by Iceland_jack): I want to make sure I understand this correctly, this brittleness applies to monad transformers and not the instances below `↓` since they are already kind polymorphic? {{{#!hs instance forall k (r :: k) (m :: k -> *). Functor (ContT r m) instance forall k (r :: k) (m :: k -> *). Applicative (ContT r m) instance forall k (r :: k) (m :: k -> *). Monad (ContT r m) }}} ---- I have no use for a kind-polymorphic instance (that I know of!), the original motivation was allowing {{{#!hs callCC :: ((a -> ContT r m b) -> ContT r m a) -> ContT r m a callCC @(ContT _ _) }}} to match the instance. {{{#!hs instance k ~ Type => MonadCont (ContT @k r m) }}} would allow `callCC @(ContT _ _)` but not `callCC :: ((a -> ContT r m b) -> ContT r m a) -> ContT r m a` it seems (I get `Couldn't match type ‘k1’ with ‘*’ arising from a use of ‘callCC’`). I don't understand your point about `MonadState` and `MonadReader`. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jul 23 20:28:09 2016 From: ghc-devs at haskell.org (GHC) Date: Sat, 23 Jul 2016 20:28:09 -0000 Subject: [GHC] #12429: Pattern synonym parse error should recommend enabling extension Message-ID: <049.a84572b34b0d4ea1faf1de7a2715c84f@haskell.org> #12429: Pattern synonym parse error should recommend enabling extension -------------------------------------+------------------------------------- Reporter: agibiansky | Owner: Type: bug | Status: new Priority: low | Milestone: Component: Compiler | Version: 7.10.3 Keywords: pattern | Operating System: Unknown/Multiple synonym error messages | Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- Currently, if you try to use pattern synonyms in a module without -XPatternSynonyms, you can get a very uninformative parse error. For example: {{{#!hs module X where import Data.Text (pattern Y) x = 3 }}} Yields, when compiled on GHC 7.10, {{{ test.hs:3:27: parse error on input "Y" }}} It would be helpful if in addition to the error, the message suggested to the user to enable the PatternSynonyms extension, as many other error messages already do. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jul 23 23:58:10 2016 From: ghc-devs at haskell.org (GHC) Date: Sat, 23 Jul 2016 23:58:10 -0000 Subject: [GHC] #12425: With -O1 and above causes ghc to use all available memory before being killed by OOM killer In-Reply-To: <044.8db07ee1e56d0d370ac594dbce3dff94@haskell.org> References: <044.8db07ee1e56d0d370ac594dbce3dff94@haskell.org> Message-ID: <059.8247541c336b441a0d619c13abc9ade8@haskell.org> #12425: With -O1 and above causes ghc to use all available memory before being killed by OOM killer -------------------------------------+------------------------------------- Reporter: erikd | Owner: Type: bug | Status: new Priority: high | Milestone: 8.0.2 Component: Compiler | Version: 8.0.1 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 erikd): @thomie Oh wow, that change you suggested (switching from `liftM` to `liftA`) prevents this problem in `conduit-find` even with stock 8.0.1. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Jul 24 00:11:41 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 24 Jul 2016 00:11:41 -0000 Subject: [GHC] #12418: Make `MonadCont (ContT r m)` polykinded (r::k), (m::k -> Type) In-Reply-To: <051.aa98db01c615f5738620e369aa22a8a6@haskell.org> References: <051.aa98db01c615f5738620e369aa22a8a6@haskell.org> Message-ID: <066.3d3dc190db797db212adbce687bac847@haskell.org> #12418: Make `MonadCont (ContT r m)` polykinded (r::k), (m::k -> Type) -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: 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: | -------------------------------------+------------------------------------- Comment (by ekmett): {{{#!hs instance MonadState s m => MonadState s (ContT @Type r m) }}} suffers the same sort of problem as the MonadCont instance, if you define it pointwise at @Type. If m and r are left underspecified kind wise and you go to invoke a `MonadState s ` operation, it has no reason to pick that instance, unless it can figure out `k = Type`, hence `m :: Type -> Type`, it won't discharge the head and go looking for `MonadState s m` from the body and use this instance. It'll just whine about a missing instance at an unknown kind. So if `m` is polykinded like `Proxy`, which has kind k -> *, but at * -> * is a perfectly legitimate monad (it is the unique-up-to-isomorphism terminal monad), then this no longer monomorphizes m to kind * -> * to go look for this possible instance. The compiler doesn't know if you doesn't know someone won't make up some completely different instance like: {{{#!hs instance MonadState () (ContT @Whatever r m) where get = return () put () = return () }}} pointwise at another kind. This 'can't do the same sort of lifting as the typical MonadState, so it really doesn't have any place being defined on this data type and any such instance will necessarily be an orphan. As you note Functor, Applicative, Monad all work fine, because really if you look at ContT the fact that m and r exist as separate entities doesn't matter to those instances at all, those are just the basic `Cont r'` instances instantiated at `r' = m r`. They never use 'm' to do any work, and just teeat `m r` as an opaque blob. Once you start lifting monad transformer instances for things like MonadState, MonadWriter, etc. over `ContT r` then we need to know `m :: Type -> Type`, because we finally start interacting with the extra structure we've given our CPS'd result type. You get a slightly more general callCC at the expense of screwing up inference for every monad transformer instance, that can only be taken advantage of to make instances that act at different kinds inconsistently with the instances that are already in place. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Jul 24 06:44:25 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 24 Jul 2016 06:44:25 -0000 Subject: [GHC] #12429: Pattern synonym parse error should recommend enabling extension In-Reply-To: <049.a84572b34b0d4ea1faf1de7a2715c84f@haskell.org> References: <049.a84572b34b0d4ea1faf1de7a2715c84f@haskell.org> Message-ID: <064.0fa51cf7d984599067da3dc96aaa7af5@haskell.org> #12429: Pattern synonym parse error should recommend enabling extension -------------------------------------+------------------------------------- Reporter: agibiansky | Owner: Type: bug | Status: new Priority: low | Milestone: Component: Compiler | Version: 7.10.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 mpickering): * keywords: pattern synonym error messages => PatternSynonyms -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Jul 24 14:31:26 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 24 Jul 2016 14:31:26 -0000 Subject: [GHC] #12394: broken (obsolete?) links to user guide In-Reply-To: <049.236b514a0a8df239b8fccae12a734bcb@haskell.org> References: <049.236b514a0a8df239b8fccae12a734bcb@haskell.org> Message-ID: <064.16538dff848584980d4959db9bc6e7b6@haskell.org> #12394: broken (obsolete?) links to user guide -------------------------------------+------------------------------------- Reporter: j.waldmann | Owner: 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 thomie): Maybe `https://downloads.haskell.org/~ghc/latest` should be a redirect instead of a copy of the latest stable version. Then referrers will more likely create links to the latest stable version, instead of to "latest". -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Jul 24 16:16:49 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 24 Jul 2016 16:16:49 -0000 Subject: [GHC] #12430: TypeFamilyDependencies accepts invalid injectivity annotation Message-ID: <048.bd286895ba8b7f6cc12aad47c9d255c3@haskell.org> #12430: TypeFamilyDependencies accepts invalid injectivity annotation -------------------------------------+------------------------------------- Reporter: vagarenko | Owner: Type: bug | Status: new Priority: high | Milestone: Component: Compiler | Version: 8.0.1 (Type checker) | 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: -------------------------------------+------------------------------------- Consider this code (depends on singletons-2.2): {{{#!hs {-# LANGUAGE TypeFamilies, DataKinds, PolyKinds, TypeOperators, KindSignatures, TypeInType, TypeFamilyDependencies, UndecidableInstances #-} module Bug where import Data.Kind (Type) import Data.Singletons.Prelude (Map, SndSym0) import GHC.TypeLits (Nat) data Payload = A | B newtype NewType a = NewType Int type NatList = [(Nat, Payload)] type StripNatList (natList :: NatList) = Map SndSym0 natList type family Family (natList :: NatList) = (r :: Type) | r -> natList where Family '[] = () Family xs = NewType (StripNatList xs) }}} Why GHC is okay with injectivity annotation for `Family`: `r -> natList`? These two types: {{{#!hs type Foo = Family '[ '(0, 'A), '(1, 'B)] type Bar = Family '[ '(0, 'A), '(0, 'B)] }}} are obviously map to the same type: {{{#!hs *Bug Data.Singletons.Prelude> :kind! Foo Foo :: * = NewType ('A :$$$ '['B]) *Bug Data.Singletons.Prelude> :kind! Bar Bar :: * = NewType ('A :$$$ '['B]) }}} ---- If inline `StripNatList` inside `Family` definition: {{{#!hs type family Family (natList :: NatList) = (r :: Type) | r -> natList where Family '[] = () Family xs = NewType (Map SndSym0 xs) }}} or change `StripNatList` definition to type family: {{{#!hs type family StripNatList (natList :: NatList) where StripNatList '[] = '[] StripNatList ('(n, x) ': xs) = x ': StripNatList xs }}} compilation expectedly fails with `Type family equation violates injectivity annotation.` ---- Moreover, if I remove `NewType` from `Family` and change result kind: {{{#!hs type family Family (natList :: NatList) = (r :: [Payload]) | r -> natList where Family xs = StripNatList xs }}} it fails with correct error regardless of `StripNatList` definition. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Jul 24 17:11:26 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 24 Jul 2016 17:11:26 -0000 Subject: [GHC] #8581: Pattern synonym used in an expression context could have different constraints to pattern used in a pattern context In-Reply-To: <045.ffb8b433d262c0e3b5b415c2eeca2eee@haskell.org> References: <045.ffb8b433d262c0e3b5b415c2eeca2eee@haskell.org> Message-ID: <060.64f46862e5d53e69e49592016efe111e@haskell.org> #8581: Pattern synonym used in an expression context could have different constraints to pattern used in a pattern context -------------------------------------+------------------------------------- Reporter: cactus | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 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 goldfire): Replying to [comment:39 dfeuer]: > I think what we actually want (borrowing from the [https://hackage.haskell.org/package/these these] package) is `These PatternType Type`. That is, either just the pattern, just the constructor, or both. But this idea opens up a new, heretofore undiscussed possibility, that of a pattern synonym that cannot be used as a pattern. In other words, it would just be a normal Haskell variable, except with a capitalized identifier. I personally think this is one bridge too far, encouraging people to use a capitalized word for ordinary functions. I think this would be confusing, and for what benefit? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Jul 24 17:15:59 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 24 Jul 2016 17:15:59 -0000 Subject: [GHC] #12430: TypeFamilyDependencies accepts invalid injectivity annotation In-Reply-To: <048.bd286895ba8b7f6cc12aad47c9d255c3@haskell.org> References: <048.bd286895ba8b7f6cc12aad47c9d255c3@haskell.org> Message-ID: <063.c85c7f04bdc27b042e2b822e161b1ce2@haskell.org> #12430: TypeFamilyDependencies accepts invalid injectivity annotation -------------------------------------+------------------------------------- Reporter: vagarenko | Owner: Type: bug | Status: new Priority: high | Milestone: Component: Compiler (Type | Version: 8.0.1 checker) | 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 goldfire): It looks like we're not being aggressive enough in unrolling type synonyms -- a legitimate bug. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Jul 24 21:59:29 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 24 Jul 2016 21:59:29 -0000 Subject: [GHC] #12425: With -O1 and above causes ghc to use all available memory before being killed by OOM killer In-Reply-To: <044.8db07ee1e56d0d370ac594dbce3dff94@haskell.org> References: <044.8db07ee1e56d0d370ac594dbce3dff94@haskell.org> Message-ID: <059.f14ebd6008848460368681d62e349390@haskell.org> #12425: With -O1 and above causes ghc to use all available memory before being killed by OOM killer -------------------------------------+------------------------------------- Reporter: erikd | Owner: Type: bug | Status: new Priority: high | Milestone: 8.0.2 Component: Compiler | Version: 8.0.1 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 nomeata): A guess would be that in 8.0’s library version, `liftM` is implemented in a way that mentions `fmap`, and `liftM` is inlined to expose that. Then all your unconditinally marked inline functions become effectively recursive, but still keep inlining. But didn’t investigate deeper. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Jul 24 22:00:30 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 24 Jul 2016 22:00:30 -0000 Subject: [GHC] #12428: Allow pattern synonyms to optionally carry coerceability In-Reply-To: <045.f7b089d2570bb063442b06cde2fff958@haskell.org> References: <045.f7b089d2570bb063442b06cde2fff958@haskell.org> Message-ID: <060.37d3b5de14d2e7704e46945a41589b0f@haskell.org> #12428: Allow pattern synonyms to optionally carry coerceability -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: 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: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by nomeata): Can you give a concrete examples? I’m not quite sure what you mean by “carry coerceability”, and how that is tied to pattern synonyms. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Jul 24 22:09:26 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 24 Jul 2016 22:09:26 -0000 Subject: [GHC] #12428: Allow pattern synonyms to optionally carry coerceability In-Reply-To: <045.f7b089d2570bb063442b06cde2fff958@haskell.org> References: <045.f7b089d2570bb063442b06cde2fff958@haskell.org> Message-ID: <060.71348aecc8137edf9fb6cc62308a5ce1@haskell.org> #12428: Allow pattern synonyms to optionally carry coerceability -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: 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: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by dfeuer): Replying to [comment:1 nomeata]: > Can you give a concrete examples? I’m not quite sure what you mean by “carry coerceability”, and how that is tied to pattern synonyms. Having a newtype constructor in scope in a module brings with it certain `Coercible` instances. There is no other way to bring those into scope globally in a module, although they can be used locally by matching on a `Coercion`. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 25 03:14:58 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 25 Jul 2016 03:14:58 -0000 Subject: [GHC] #12123: GHC crashes when calling typeRep on a promoted tuple In-Reply-To: <050.7224be05b7e58580597e49fc3f0142fe@haskell.org> References: <050.7224be05b7e58580597e49fc3f0142fe@haskell.org> Message-ID: <065.8e02090b4018311cd8344d6b90f41701@haskell.org> #12123: GHC crashes when calling typeRep on a promoted tuple -------------------------------------+------------------------------------- Reporter: MikeIzbicki | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: duplicate | Keywords: Typeable 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 zilinc): * status: new => closed * resolution: => duplicate Comment: seems to be a duplicate of #12132 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 25 03:18:00 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 25 Jul 2016 03:18:00 -0000 Subject: [GHC] #8581: Pattern synonym used in an expression context could have different constraints to pattern used in a pattern context In-Reply-To: <045.ffb8b433d262c0e3b5b415c2eeca2eee@haskell.org> References: <045.ffb8b433d262c0e3b5b415c2eeca2eee@haskell.org> Message-ID: <060.1129c4cad6eca5be17ab8afc4a0b5ec2@haskell.org> #8581: Pattern synonym used in an expression context could have different constraints to pattern used in a pattern context -------------------------------------+------------------------------------- Reporter: cactus | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 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 dfeuer): Replying to [comment:40 goldfire]: > But this idea opens up a new, heretofore undiscussed possibility, that of a pattern synonym that cannot be used as a pattern. In other words, it would just be a normal Haskell variable, except with a capitalized identifier. I personally think this is one bridge too far, encouraging people to use a capitalized word for ordinary functions. I think this would be confusing, and for what benefit? It emphasizes the orthogonality of pattern synonyms and constructor synonyms; I tend to find orthogonal features easier to understand. The current reuse of the `where` keyword to add a constructor synonym is also troubling. It would feel cleaner to me to let these be completely separate declarations. BTW, what ever happened to the idea of letting a module re-export a type and associate pattern synonyms with it? I lost track of that and haven't had a chance to upgrade to 8.0 yet. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 25 08:51:24 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 25 Jul 2016 08:51:24 -0000 Subject: [GHC] #11425: The GHC API doesn't provide a good hscTarget option for tooling In-Reply-To: <046.59f16ebaf7d24ed3fda7cb6515755975@haskell.org> References: <046.59f16ebaf7d24ed3fda7cb6515755975@haskell.org> Message-ID: <061.6dd3fc7d50e27a5662512f59907a9573@haskell.org> #11425: The GHC API doesn't provide a good hscTarget option for tooling -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: feature request | Status: new Priority: high | Milestone: 8.2.1 Component: GHC API | Version: 7.10.3 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 osa1: @@ -16,1 +16,1 @@ - * [https://github.com/DanielG/ghc-mod/pull/145|Fails} to issue pattern + * [https://github.com/DanielG/ghc-mod/pull/145 Fails] to issue pattern New description: Tools like ghc-mod typically just want `TypecheckedModule`s. Sadly, the GHC API currently doesn't provide a good way to get at these in all cases (see this [https://github.com/DanielG/ghc-mod/issues/205|ghc-mod ticket]). Each of the options we offer are cursed with their own limitations (largely quoting from the ghc-mod ticket), == HscNothing == At first glance this looks like what you would want. But... * Pros * Doesn't generate code of any sort and is therefore rather lightweight * Cons * It lacks support for Template Haskell * Has trouble with `foreign export`s * [https://github.com/DanielG/ghc-mod/pull/145 Fails] to issue pattern match checker warnings == HscInterpreted == Okay, so `HscNothing` doesn't work. Maybe `HscInterpreted` is better? * Pros * Supports Template Haskell * Cons * Can't deal with unboxed tuples (#1257) * Slower as we need to produce unnecessary bytecode * Large memory footprint * Also can't deal with `foreign export`s == HscAsm == * Pros * Supports all compilable code * Cons * Slow * Produces `.o` files This is quite unfortunate. It seems like we need something in between `HscNothing` and `HscInterpreted` which is willing to use the interpreter to evaluate Template Haskell splices when necessary, but doesn't produce bytecode. Unfortunately it's unclear what to do about `foreign export` (but arguably most tools would be fine with some approximate representation). -- -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 25 10:23:50 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 25 Jul 2016 10:23:50 -0000 Subject: [GHC] #12425: With -O1 and above causes ghc to use all available memory before being killed by OOM killer In-Reply-To: <044.8db07ee1e56d0d370ac594dbce3dff94@haskell.org> References: <044.8db07ee1e56d0d370ac594dbce3dff94@haskell.org> Message-ID: <059.2f417f90f461e2512ff477ecd4c93ced@haskell.org> #12425: With -O1 and above causes ghc to use all available memory before being killed by OOM killer -------------------------------------+------------------------------------- Reporter: erikd | Owner: Type: bug | Status: new Priority: high | Milestone: 8.0.2 Component: Compiler | Version: 8.0.1 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 erikd): Thats seems to be a possible explanation. Is there no loop checker for the inliner? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 25 12:15:10 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 25 Jul 2016 12:15:10 -0000 Subject: [GHC] #8581: Pattern synonym used in an expression context could have different constraints to pattern used in a pattern context In-Reply-To: <045.ffb8b433d262c0e3b5b415c2eeca2eee@haskell.org> References: <045.ffb8b433d262c0e3b5b415c2eeca2eee@haskell.org> Message-ID: <060.7b7778b720e95e9965a2b014d25757be@haskell.org> #8581: Pattern synonym used in an expression context could have different constraints to pattern used in a pattern context -------------------------------------+------------------------------------- Reporter: cactus | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 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 goldfire): Replying to [comment:41 dfeuer]: > [Allowing an expression-only "pattern synonym"] emphasizes the orthogonality of pattern synonyms and constructor synonyms; I tend to find orthogonal features easier to understand. The current reuse of the `where` keyword to add a constructor synonym is also troubling. It would feel cleaner to me to let these be completely separate declarations. OK. I still don't want this feature, but I understand your reason. > > BTW, what ever happened to the idea of letting a module re-export a type and associate pattern synonyms with it? I lost track of that and haven't had a chance to upgrade to 8.0 yet. This is implemented, as described (very briefly) in the second half of [https://downloads.haskell.org/~ghc/latest/docs/html/users_guide/glasgow_exts.html #import-and-export-of-pattern-synonyms this section] of the user manual. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 25 16:29:49 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 25 Jul 2016 16:29:49 -0000 Subject: [GHC] #11470: Support changing cross compiler target at runtime In-Reply-To: <045.fac441a3726b1539e9f173129f6fb28c@haskell.org> References: <045.fac441a3726b1539e9f173129f6fb28c@haskell.org> Message-ID: <060.2bd9b9d4a02e347a8a12a49bb89c78ef@haskell.org> #11470: Support changing cross compiler target at runtime -------------------------------------+------------------------------------- Reporter: ezyang | Owner: Type: feature request | Status: new Priority: normal | Milestone: 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: #11378 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * cc: bgamari (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 25 16:37:16 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 25 Jul 2016 16:37:16 -0000 Subject: [GHC] #11425: The GHC API doesn't provide a good hscTarget option for tooling In-Reply-To: <046.59f16ebaf7d24ed3fda7cb6515755975@haskell.org> References: <046.59f16ebaf7d24ed3fda7cb6515755975@haskell.org> Message-ID: <061.6894de3ba95143ec78cac7ee7d86394a@haskell.org> #11425: The GHC API doesn't provide a good hscTarget option for tooling -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: feature request | Status: new Priority: high | Milestone: 8.2.1 Component: GHC API | Version: 7.10.3 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 ezyang): Re pattern checker warnings see #10600. Re nothing versus interpreted, if Haskell separated the compile-time/run- time phases more closely, it would be easier to only interpret code that was going to be used for TH. http://blog.ezyang.com/2016/07/what-template- haskell-gets-wrong-and-racket-gets-right/ -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 25 16:38:24 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 25 Jul 2016 16:38:24 -0000 Subject: [GHC] #12431: Type checker rejects valid program Message-ID: <046.97f73897f6d8587ad4e6089f7601bdf8@haskell.org> #12431: Type checker rejects valid program -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: bug | Status: new Priority: highest | Milestone: 8.2.1 Component: Compiler | Version: 8.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: -------------------------------------+------------------------------------- Since at least 6e280c2c5b2903ae38f4da15a41ea94793907407 GHC fails to compile `resourcet` due to a likely erroneous type error. Here is a minimal case that reproduces the error, {{{#!hs {-# LANGUAGE RankNTypes #-} {-# LANGUAGE FlexibleContexts #-} module Hi where import Control.Monad (liftM, ap) data Allocated a = Allocated a newtype Acquire a = Acquire ((forall b. IO b -> IO b) -> IO (Allocated a)) instance Functor Acquire where fmap = liftM instance Applicative Acquire where pure a = Acquire (\_ -> return (Allocated a)) (<*>) = ap instance Monad Acquire where return = pure Acquire f >>= g' = Acquire $ \restore -> do Allocated x <- f restore let Acquire g = g' x Allocated y <- g restore return $! Allocated y }}} This fails with, {{{ $ ghc Hi.hs [1 of 1] Compiling Hi ( Hi.hs, Hi.o ) Hi.hs:22:21: error: • Couldn't match expected type ‘t’ with actual type ‘(forall b1. IO b1 -> IO b1) -> IO (Allocated b)’ ‘t’ is a rigid type variable bound by the inferred type of g :: t at Hi.hs:22:13-28 • In the pattern: Acquire g In a pattern binding: Acquire g = g' x In the expression: do { Allocated x <- f restore; let Acquire g = g' x; Allocated y <- g restore; return $! Allocated y } • Relevant bindings include g' :: a -> Acquire b (bound at Hi.hs:20:19) (>>=) :: Acquire a -> (a -> Acquire b) -> Acquire b (bound at Hi.hs:20:15) }}} Despite compiling with 8.0.1 and earlier versions. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 25 16:43:16 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 25 Jul 2016 16:43:16 -0000 Subject: [GHC] #12431: Type checker rejects valid program In-Reply-To: <046.97f73897f6d8587ad4e6089f7601bdf8@haskell.org> References: <046.97f73897f6d8587ad4e6089f7601bdf8@haskell.org> Message-ID: <061.d30f1e9212b291498e8f7c1a93c51fdb@haskell.org> #12431: Type checker rejects valid program -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: bug | Status: new Priority: highest | Milestone: 8.2.1 Component: Compiler (Type | Version: 8.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: | -------------------------------------+------------------------------------- Comment (by rwbarton): I assume this is a duplicate of #12427. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 25 18:56:29 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 25 Jul 2016 18:56:29 -0000 Subject: [GHC] #12363: Type application for infix In-Reply-To: <051.833fc99ca846ecc78974bf61eb05e05f@haskell.org> References: <051.833fc99ca846ecc78974bf61eb05e05f@haskell.org> Message-ID: <066.129a1148fec3f28a4099da05c6e198c4@haskell.org> #12363: Type application for infix -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: 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: | -------------------------------------+------------------------------------- Comment (by Iceland_jack): This is interesting. Usually Haddock displays {{{#!hs ((~) * a b, Data a) => Data ((:~:) * a b) }}} This could be {{{#!hs (a ~ @* b, Data a) => Data (q :~: @* b) }}} The asymmetry is awkward but I prefer it to the current version. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 25 19:13:54 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 25 Jul 2016 19:13:54 -0000 Subject: [GHC] #12432: TypeInType: open type family application as type family return kind fails to compile Message-ID: <046.81766c43f1232218e828bba3b4f71960@haskell.org> #12432: TypeInType: open type family application as type family return kind fails to compile -------------------------------------+------------------------------------- Reporter: j6carey | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 (Type checker) | Keywords: | Operating System: Linux Architecture: | Type of failure: GHC rejects Unknown/Multiple | valid program Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- With TypeInType enabled, I can use a closed type family to compute the return kind of a type family from its arguments. But an equivalent open type family used in the same way triggers a compilation failure, as if the relevant instance of that open type family were not considered. (Of course, there may be some subtle prohibition of which I am not aware at the present time.) I will attach a test case. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 25 19:15:30 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 25 Jul 2016 19:15:30 -0000 Subject: [GHC] #12432: TypeInType: open type family application as type family return kind fails to compile In-Reply-To: <046.81766c43f1232218e828bba3b4f71960@haskell.org> References: <046.81766c43f1232218e828bba3b4f71960@haskell.org> Message-ID: <061.765f0525383c44d37a68531a2556adbd@haskell.org> #12432: TypeInType: open type family application as type family return kind fails to compile -------------------------------------+------------------------------------- Reporter: j6carey | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.1 checker) | Resolution: | Keywords: Operating System: Linux | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by j6carey): * Attachment "test.hs" added. Test case that does not compile with GHC 8.0.1 due to use of an open type family to supply the return kind of another type family -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 25 20:53:36 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 25 Jul 2016 20:53:36 -0000 Subject: [GHC] #12432: TypeInType: open type family application as type family return kind fails to compile In-Reply-To: <046.81766c43f1232218e828bba3b4f71960@haskell.org> References: <046.81766c43f1232218e828bba3b4f71960@haskell.org> Message-ID: <061.e1bc1ffbd6ddd1b630a618d067b1e33c@haskell.org> #12432: TypeInType: open type family application as type family return kind fails to compile -------------------------------------+------------------------------------- Reporter: j6carey | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.1 checker) | Resolution: duplicate | Keywords: Operating System: Linux | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by goldfire): * status: new => closed * resolution: => duplicate Comment: This is due to the fact that GHC processes instances after other type declarations. Fixed in HEAD by @alexvieth. Workaround: use multiple modules or use an empty top-level declaration splice `$(return [])` to force GHC to compile the instances earlier. Thanks for reporting! -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 25 21:00:37 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 25 Jul 2016 21:00:37 -0000 Subject: [GHC] #12432: TypeInType: open type family application as type family return kind fails to compile In-Reply-To: <046.81766c43f1232218e828bba3b4f71960@haskell.org> References: <046.81766c43f1232218e828bba3b4f71960@haskell.org> Message-ID: <061.1b741348135e86ceff4d02e905e91507@haskell.org> #12432: TypeInType: open type family application as type family return kind fails to compile -------------------------------------+------------------------------------- Reporter: j6carey | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.1 checker) | Resolution: duplicate | Keywords: Operating System: Linux | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by j6carey): Thanks! -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 25 21:57:06 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 25 Jul 2016 21:57:06 -0000 Subject: [GHC] #12433: GHCi produces incorrect results when evaluating with compiled code Message-ID: <047.882472dc094976fa082efbe928facde9@haskell.org> #12433: GHCi produces incorrect results when evaluating with compiled code -------------------------------------+------------------------------------- Reporter: diatchki | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Keywords: ghci, dynamic | Operating System: Linux linking, compiled code | Architecture: x86_64 | Type of failure: Incorrect result (amd64) | at runtime Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- When GHCi evaluates in non-interpreted mode, it sometimes produces incorrect results. The following example---extracted from a much larger program---illustrates the problem: {{{#!hs import Lex num = 100000 txt1 = "aaa,aaa" main :: IO () main = print $ sum $ map (length . haskellLex) $ replicate num txt1 }}} This program lexes the same string 100000 times, and prints the total number of tokens. Since we are lexing the same string, we'd expect to always get the same result, but due to this bug, this is not the case! We repeat the process 100000 times so that we can encounter the bug somewhat reliably---the problem does not occur every time. To reproduce the problem, we need to load `Lex` in compiled form, not interpreted and with some optimizations: {{{ ghc -c -O1 -dynamic Lex.hs }}} The source code for the "lexer" is as follows: {{{#!haskell module Lex (haskellLex) where cclass :: Char -> Int cclass c = case c of 'a' -> 10 ',' -> 11 'A' -> 0 'B' -> 0 'C' -> 0 'D' -> 0 'E' -> 0 'F' -> 0 haskellLex :: String -> [()] haskellLex [] = [] haskellLex (i:is) = case cclass i of 10 -> haskellLex62 is 11 -> () : haskellLex is haskellLex62 :: String -> [()] haskellLex62 [] = [()] haskellLex62 (i:is) = case cclass i of 0 -> [()] 1 -> [()] 2 -> [()] 3 -> [()] 4 -> [()] 10 -> haskellLex62 is 11 -> () : haskellLex (i:is) x -> error ("[GHC BUG] cclass returned: " ++ show (i,x) }}} This is a minimized version from a full lexer. As odd as it looks, removing pretty much anything seems to cause the bug to go away. This is what happens when we run the program: {{{ runhaskell test.hs test.hs: [GHC BUG] cclass returned: (',',-556) CallStack (from HasCallStack): error, called at Lex.hs:36:12 in main:Lex }}} The problem is that after many evaluations, the function `cclass` returned `-556` for character `,`, when it should have returned `11`. I've been able to reproduce this on two Linux machines, both running 64-bit Ubuntu (16.04). The issue does not seem to happen on Mac OS. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 25 21:58:23 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 25 Jul 2016 21:58:23 -0000 Subject: [GHC] #12433: GHCi produces incorrect results when evaluating with compiled code In-Reply-To: <047.882472dc094976fa082efbe928facde9@haskell.org> References: <047.882472dc094976fa082efbe928facde9@haskell.org> Message-ID: <062.4459762534a77c99eaea2759971aa52a@haskell.org> #12433: GHCi produces incorrect results when evaluating with compiled code -------------------------------------+------------------------------------- Reporter: diatchki | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: ghci, dynamic | linking, compiled code Operating System: Linux | Architecture: x86_64 Type of failure: Incorrect result | (amd64) at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by diatchki): * Attachment "bug.tar.gz" added. Source code and a `Makefile` to reproduce the bug -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 25 22:36:54 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 25 Jul 2016 22:36:54 -0000 Subject: [GHC] #12432: TypeInType: open type family application as type family return kind fails to compile In-Reply-To: <046.81766c43f1232218e828bba3b4f71960@haskell.org> References: <046.81766c43f1232218e828bba3b4f71960@haskell.org> Message-ID: <061.99da15a1f0abd69b613bdc525bc71387@haskell.org> #12432: TypeInType: open type family application as type family return kind fails to compile -------------------------------------+------------------------------------- Reporter: j6carey | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.1 checker) | Resolution: duplicate | Keywords: Operating System: Linux | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by j6carey): * Attachment "Test3.hs" added. One more thing: does the same fix help with class instance contexts as well? Please see the new attachment Test3.hs. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 25 22:42:31 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 25 Jul 2016 22:42:31 -0000 Subject: [GHC] #12434: Test suite should not copy in un-versioned files Message-ID: <045.73ead521acc3bdb4cc5f6bae27de6ab9@haskell.org> #12434: Test suite should not copy in un-versioned files -------------------------------------+------------------------------------- Reporter: ezyang | Owner: thomie Type: bug | Status: new Priority: normal | Milestone: Component: Test Suite | 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: -------------------------------------+------------------------------------- This is something like a follow on to #12112. Basically, this bug was fixed by blacklisting the copying of some files. Well I observed that for some test-cases I was working on, where I specified `-outputdir`, my local output directory was being copied... because its file name didn't match. Wouldn't it be better to just not copy any files which are not versioned? I guess this won't work if the test suite is being run from not Git, but if Git is available that seems like a more accurate test. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 25 22:51:58 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 25 Jul 2016 22:51:58 -0000 Subject: [GHC] #12433: GHCi produces incorrect results when evaluating with compiled code In-Reply-To: <047.882472dc094976fa082efbe928facde9@haskell.org> References: <047.882472dc094976fa082efbe928facde9@haskell.org> Message-ID: <062.d83ff5367038a1037c9ccac34c7f1c64@haskell.org> #12433: GHCi produces incorrect results when evaluating with compiled code -------------------------------------+------------------------------------- Reporter: diatchki | Owner: Type: bug | Status: new Priority: highest | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: ghci, dynamic | linking, compiled code Operating System: Linux | Architecture: x86_64 Type of failure: Incorrect result | (amd64) at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by rwbarton): * priority: normal => highest Comment: I can even reproduce it without ghci. Just compile `Lex.hs` with `-O` and `test.hs` without; both still `-dynamic`. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 26 00:07:40 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 26 Jul 2016 00:07:40 -0000 Subject: [GHC] #12433: GHCi produces incorrect results when evaluating with compiled code In-Reply-To: <047.882472dc094976fa082efbe928facde9@haskell.org> References: <047.882472dc094976fa082efbe928facde9@haskell.org> Message-ID: <062.e5cc1140d3b2fb320b7fe98ec78a9c4b@haskell.org> #12433: GHCi produces incorrect results when evaluating with compiled code -------------------------------------+------------------------------------- Reporter: diatchki | Owner: Type: bug | Status: new Priority: highest | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: ghci, dynamic | linking, compiled code Operating System: Linux | Architecture: x86_64 Type of failure: Incorrect result | (amd64) at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by ekmett): * cc: ekmett (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 26 00:20:28 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 26 Jul 2016 00:20:28 -0000 Subject: [GHC] #12433: GHCi produces incorrect results when evaluating with compiled code In-Reply-To: <047.882472dc094976fa082efbe928facde9@haskell.org> References: <047.882472dc094976fa082efbe928facde9@haskell.org> Message-ID: <062.9e6be43c548cae101de8315682e6b9c2@haskell.org> #12433: GHCi produces incorrect results when evaluating with compiled code -------------------------------------+------------------------------------- Reporter: diatchki | Owner: Type: bug | Status: new Priority: highest | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: ghci, dynamic | linking, compiled code Operating System: Linux | Architecture: x86_64 Type of failure: Incorrect result | (amd64) at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by rwbarton): The problem is in PIC code generation for jump tables (CmmSwitch). Here is the problematic part of `haskellLex62`: {{{ call $wcclass_r2lE_info(R2) returns to c2s5, args: 8, res: 8, upd: 8; c2s5: _s2mn::I64 = I64[Sp + 8]; _s2mo::I64 = R1; if (%MO_S_Ge_W64(R1, 12)) goto c2sB; else goto u2t1; u2t1: if (%MO_S_Lt_W64(_s2mo::I64, 0)) goto c2sB; else goto u2t2; u2t2: switch [0 .. 11] _s2mo::I64 { case 0, 1, 2, 3, 4 : goto u2t7; case 10 : goto c2sT; case 11 : goto c2sV; default: goto c2sB; } c2sV: Hp = Hp + 48; if (Hp > HpLim) goto c2sY; else goto c2sX; c2sY: HpAlloc = 48; R1 = _s2mo::I64; call stg_gc_unbx_r1(R1) returns to c2s5, args: 8, res: 8, upd: 8; c2sX: I64[Hp - 40] = sat_s2mp_info; P64[Hp - 24] = P64[Sp + 24]; I64[Hp - 16] = :_con_info; P64[Hp - 8] = GHC.Tuple.()_closure+1; P64[Hp] = Hp - 40; R1 = Hp - 14; Sp = Sp + 32; call (P64[Sp])(R1) args: 8, res: 0, upd: 8; }}} Observe that `c2s5` is the continuation for the call to `$wcclass_r2lE`, but it can also be returned to from the garbage collector after a failed heap check. The variable `_s2mo` is initialized at `c2s5` and then still live in the failed heap check block `c2sY`. However, the assembly generated for the switch looks like {{{ _c2s5: movq 8(%rbp),%rax movq %rbx,%rcx ; %rcx is _s2mo, set to R1 = %rbx cmpq $18,%rbx jge _c2sB _u2t1: testq %rcx,%rcx jl _c2sB _u2t2: leaq _n2tK(%rip),%rbx movslq (%rbx,%rcx,8),%rcx addq %rcx,%rbx jmp *%rbx ;; then a big jump table named _n2tK; in the case of 11, it jumps to _c2sV _c2sY: movq $48,904(%r13) movq %rcx,%rbx jmp *stg_gc_unbx_r1 at gotpcrel(%rip) _c2sV: addq $48,%r12 cmpq 856(%r13),%r12 ja _c2sY }}} In the failed heap check code at `_c2sY`, ghc thinks that `_s2mo` is still in `%rcx`. But actually it was clobbered by the jump table calculation at `_u2t2`. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 26 00:28:41 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 26 Jul 2016 00:28:41 -0000 Subject: [GHC] #12433: GHCi produces incorrect results when evaluating with compiled code In-Reply-To: <047.882472dc094976fa082efbe928facde9@haskell.org> References: <047.882472dc094976fa082efbe928facde9@haskell.org> Message-ID: <062.0048f5d335d74b1760a6dfae6db5150f@haskell.org> #12433: GHCi produces incorrect results when evaluating with compiled code -------------------------------------+------------------------------------- Reporter: diatchki | Owner: Type: bug | Status: new Priority: highest | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: ghci, dynamic | linking, compiled code Operating System: Linux | Architecture: x86_64 Type of failure: Incorrect result | (amd64) at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by rwbarton): So, if the heap check should happen to fail, the R1 that is passed to `stg_gc_unbx_r1` is not actually the value returned by `$wcclass`, but rather some other value (the offset from the jump table start to the branch that was taken). Then when the GC finishes and returns to `c2s5`, it looks as though `$wcclass` returned that value, which causes the error you saw. I haven't looked at the code yet to determine who is at fault--maybe liveness calculation does not flow through `switch` statements properly, or maybe the NCG is clobbering registers that it isn't entitled to clobber. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 26 01:24:37 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 26 Jul 2016 01:24:37 -0000 Subject: [GHC] #12433: GHCi produces incorrect results when evaluating with compiled code In-Reply-To: <047.882472dc094976fa082efbe928facde9@haskell.org> References: <047.882472dc094976fa082efbe928facde9@haskell.org> Message-ID: <062.8a37eaa8bafe3215c727252ea7918bad@haskell.org> #12433: GHCi produces incorrect results when evaluating with compiled code -------------------------------------+------------------------------------- Reporter: diatchki | Owner: Type: bug | Status: new Priority: highest | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: ghci, dynamic | linking, compiled code Operating System: Linux | Architecture: x86_64 Type of failure: Incorrect result | (amd64) at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by rwbarton): I think it's `genSwitch` that is at fault here. It calculates the operand adjusted for the start of the jump table with `getSomeReg`, but that doesn't mean it is entitled to clobber the returned `reg` later, after `-- HACK: On x86_64 binutils<2.17 is only able to generate...`. Here is a single-module reproducer that does not involve the GC. It should be compiled with `-dynamic` (or `-fPIC`) and `-O`. {{{#!hs f :: Int -> IO () f p = case p of 0 -> return () 1 -> return () 2 -> return () 3 -> return () 4 -> return () 10 -> return () 11 -> return () _ -> print p {-# NOINLINE f #-} main = f 8 }}} I had to use a value that falls into the default case, as GHC creates an unfolding for a scrutinee that has been successfully matched against a numeric literal and then I couldn't find any way to get the generated code to refer to the original scrutinee. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 26 02:00:51 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 26 Jul 2016 02:00:51 -0000 Subject: [GHC] #11470: Support changing cross compiler target at runtime In-Reply-To: <045.fac441a3726b1539e9f173129f6fb28c@haskell.org> References: <045.fac441a3726b1539e9f173129f6fb28c@haskell.org> Message-ID: <060.cddddcc27d42a87ebccf946e199e412c@haskell.org> #11470: Support changing cross compiler target at runtime -------------------------------------+------------------------------------- Reporter: ezyang | Owner: Type: feature request | Status: new Priority: normal | Milestone: 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: #11378 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by angerman): Just to add a note on LLVM. If we would have an architecture independent IR[1] backend, and would just emit bitcode (which we could do from textual or bitcode IR), we could ask LLVM to produce the relevant executables for the relevant targets. There is however the question about how much architecture dependent information is used up until the Cmm phase from which the LLVM backend takes over and how much architecture dependent information we use in the llvm backend. We'd finally have to see about the mangler as well. If we therefore got a bitcode emitting ghc, we would almost get all llvm backends for free. ---- [1]: As far as I understand, you can have architecture independent IR; which however requires careful instruction selection. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 26 02:15:40 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 26 Jul 2016 02:15:40 -0000 Subject: [GHC] #12432: TypeInType: open type family application as type family return kind fails to compile In-Reply-To: <046.81766c43f1232218e828bba3b4f71960@haskell.org> References: <046.81766c43f1232218e828bba3b4f71960@haskell.org> Message-ID: <061.6f9c8f30383ded7ffc5caa83cf763035@haskell.org> #12432: TypeInType: open type family application as type family return kind fails to compile -------------------------------------+------------------------------------- Reporter: j6carey | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.1 checker) | Resolution: duplicate | Keywords: Operating System: Linux | 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): That last test case is an unrelated issue, not yet fixed. The problem is that `-XTypeInType` can't use a kind equality "right away". Equality constraints in Haskell are ''lifted'', meaning that we must make sure they are not bottom before using them to cast anything. Normally, this is all optimized away. But it does mean that we can't immediately use a kind equality in a type unless there is a place to put a check for bottom. Your code has no such place. This is all a bit of a dark corner, and I'm afraid you shouldn't hold your breath for a solution. On the flip side, it would be very enlightening if you have a realistic scenario where this limitation bites. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 26 02:33:04 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 26 Jul 2016 02:33:04 -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.c80a298c8933122a3f19d191a6fd5918@haskell.org> #11758: Drop x86_64 binutils <2.17 hack -------------------------------------+------------------------------------- Reporter: bgamari | Owner: avd Type: task | Status: new Priority: normal | Milestone: 8.2.1 Component: Compiler (NCG) | Version: 8.0.1-rc2 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 rwbarton): This hack is responsible for #12433. However, there is also perhaps an argument for taking advantage of the small code model where possible to generate jump tables of half the size. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 26 08:07:52 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 26 Jul 2016 08:07:52 -0000 Subject: [GHC] #12427: Type inference regression with RankNTypes (GHC 8.1) In-Reply-To: <045.c0f95031d5d84dce2d172c79ab762b36@haskell.org> References: <045.c0f95031d5d84dce2d172c79ab762b36@haskell.org> Message-ID: <060.cd5811e60b1486e8a76657651a15327e@haskell.org> #12427: Type inference regression with RankNTypes (GHC 8.1) -------------------------------------+------------------------------------- Reporter: thomie | Owner: Type: bug | Status: new Priority: highest | Milestone: 8.2.1 Component: Compiler (Type | Version: 8.1 checker) | Resolution: | Keywords: RankNTypes Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: #12431 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * cc: bgamari, simonpj (added) * priority: normal => highest * related: => #12431 * milestone: => 8.2.1 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 26 08:08:28 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 26 Jul 2016 08:08:28 -0000 Subject: [GHC] #12431: Type checker rejects valid program In-Reply-To: <046.97f73897f6d8587ad4e6089f7601bdf8@haskell.org> References: <046.97f73897f6d8587ad4e6089f7601bdf8@haskell.org> Message-ID: <061.ad4d7417a2cd2ea49c2dcee20de97d9f@haskell.org> #12431: Type checker rejects valid program -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: bug | Status: closed Priority: highest | Milestone: 8.2.1 Component: Compiler (Type | Version: 8.1 checker) | Resolution: duplicate | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: #12427 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => closed * resolution: => duplicate * related: => #12427 Comment: Indeed, looks about right. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 26 09:43:39 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 26 Jul 2016 09:43:39 -0000 Subject: [GHC] #12435: Turn "No alternatives for a case scrutinee not known to diverge for sure" into a warning Message-ID: <046.86fe10487270419d402270c6ee8b1e23@haskell.org> #12435: Turn "No alternatives for a case scrutinee not known to diverge for sure" into a warning -------------------------------------+------------------------------------- Reporter: nomeata | Owner: Type: task | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.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: -------------------------------------+------------------------------------- This was discussed in the context of #10180, #11290 and Phab:D851; let’s focus on this here. In changeset:a0678f1f0e62496c108491e1c80d5eef3936474a/ghc we introduced a lint ''error'' that would abort compilation if there is an empty case with a scrutinee not known to diverge for sure. It is then nature of such a test that it is never complete (we’d solve the halting problem). Occasionally, when working on other parts of the code, together with other transformations (such as CSE), we get Core code that does not pass the test, even though the scrutinee ''is'' diverging. Whenever it occurs, we have to find out why needs to be done to make the test pass again, e.g. by ensuring that CSE cse’s things in the right order, or whatnot. This slows down development (e.g. I cannot test my work on #12368 on the auto-builders because of this). It feels wrong to me to give a necessarily non-complete test such a high priority. I therefore propose to turn this check into a lint ''warning''. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 26 13:41:41 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 26 Jul 2016 13:41:41 -0000 Subject: [GHC] #12436: Too many nested forkProcess's eventually cause SIGSEGV in the child Message-ID: <044.dab3677b0c46a2e0eecf7b085cff9f68@haskell.org> #12436: Too many nested forkProcess's eventually cause SIGSEGV in the child -------------------------------------+------------------------------------- Reporter: tolik | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Runtime | Version: System | Keywords: forkProcess, | Operating System: Linux SIGSEGV | Architecture: x86_64 | Type of failure: Runtime crash (amd64) | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- Original Haskell-cafe thread: https://groups.google.com/forum/#!msg /haskell-cafe/kHMsYRMcdPs/vWD9T7saCAAJ Here is a slightly modified test program from that thread: {{{#!hs -- fork-bug.hs import System.Environment (getArgs) import System.Posix.Process (forkProcess) fork_ 0 = putStrLn "Done forking" fork_ n = forkProcess (fork_ (n - 1)) >> return () main = do [n] <- getArgs fork_ (read n) }}} With n big enough the program doesn't print anything and crashes with SIGSEGV at (semi-)random places (the crash is somewhat hard to demonstrate from the shell): {{{ $ ./fork-bug 100; sleep 0.1 Done forking $ ./fork-bug 500; sleep 0.1 Done forking $ ./fork-bug 1000; sleep 0.1 $ }}} Looks like the problem lies in C-stack exhaustion in children - lowering the stack limit makes the crash happen much earlier: {{{ $ (ulimit -s 128; ./fork-bug 5; sleep 0.1) Done forking $ (ulimit -s 128; ./fork-bug 6; sleep 0.1) Done forking $ (ulimit -s 128; ./fork-bug 7; sleep 0.1) $ (ulimit -s 128; ./fork-bug 8; sleep 0.1) $ }}} Tracing with gdb shows that with each forkProcess the stack in the forked child goes deeper and deeper, although gdb shows call stacks of constant depth: {{{ $ gdb -q fork-bug Reading symbols from fork-bug...(no debugging symbols found)...done. (gdb) set follow-fork-mode child (gdb) break forkProcess Breakpoint 1 at 0x470a60 (gdb) display $rsp (gdb) run 3 Starting program: /tmp/fork-bug 3 [Thread debugging using libthread_db enabled] Using host libthread_db library "/lib/x86_64-linux-gnu/libthread_db.so.1". Breakpoint 1, 0x0000000000470a60 in forkProcess () 1: $rsp = (void *) 0x7fffffff9e28 (gdb) bt #0 0x0000000000470a60 in forkProcess () #1 0x0000000000406215 in s3sP_info () #2 0x0000000000000000 in ?? () (gdb) continue Continuing. [New process 20434] [Thread debugging using libthread_db enabled] Using host libthread_db library "/lib/x86_64-linux-gnu/libthread_db.so.1". [Switching to Thread 0x7ffff7fd5740 (LWP 20434)] Breakpoint 1, 0x0000000000470a60 in forkProcess () 1: $rsp = (void *) 0x7fffffff5d08 (gdb) bt #0 0x0000000000470a60 in forkProcess () #1 0x0000000000406215 in s3sP_info () #2 0x0000000000000000 in ?? () (gdb) continue Continuing. [New process 20435] [Thread debugging using libthread_db enabled] Using host libthread_db library "/lib/x86_64-linux-gnu/libthread_db.so.1". [Switching to Thread 0x7ffff7fd5740 (LWP 20435)] Breakpoint 1, 0x0000000000470a60 in forkProcess () 1: $rsp = (void *) 0x7fffffff1be8 (gdb) bt #0 0x0000000000470a60 in forkProcess () #1 0x0000000000406215 in s3sP_info () #2 0x0000000000000000 in ?? () (gdb) continue Continuing. [New process 20436] [Thread debugging using libthread_db enabled] Using host libthread_db library "/lib/x86_64-linux-gnu/libthread_db.so.1". Done forking [Inferior 4 (process 20436) exited normally] }}} These results are from Ubuntu 14.04.4 with GHC 7.6.3, although OP reported using 7.10.3 and HEAD. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 26 14:02:30 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 26 Jul 2016 14:02:30 -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.f43dd62c78af246c0885704ca6f1391e@haskell.org> #11758: Drop x86_64 binutils <2.17 hack -------------------------------------+------------------------------------- Reporter: bgamari | Owner: avd Type: task | Status: new Priority: normal | Milestone: 8.2.1 Component: Compiler (NCG) | Version: 8.0.1-rc2 Resolution: | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: 12433 | Differential Rev(s): Phab:D2426 Wiki Page: | -------------------------------------+------------------------------------- Changes (by avd): * differential: => Phab:D2426 * related: => 12433 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 26 14:52:15 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 26 Jul 2016 14:52:15 -0000 Subject: [GHC] #12437: 20% regression in max_bytes_used for T1969 Message-ID: <047.090b2624111211cac9a272929b897b02@haskell.org> #12437: 20% regression in max_bytes_used for T1969 -------------------------------------+------------------------------------- Reporter: simonmar | Owner: osa1 Type: bug | Status: new Priority: highest | 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: -------------------------------------+------------------------------------- This is 20% worse: {{{ =====> T1969(normal) 1 of 1 [0, 0, 0] cd "./T1969.run" && "/data/users/smarlow/ghc/inplace/test spaces/ghc- stage2" -c T1969.hs -dno-debug-output -no-user-package-db -rtsopts -fno- warn-missed-specialisations -fshow-warning-groups +RTS -G1 -RTS +RTS -V0 -tT1969.comp.stats --machine-readable -RTS max_bytes_used value is too high: Expected T1969(normal) max_bytes_used: 15017528 +/-15% Lower bound T1969(normal) max_bytes_used: 12764898 Upper bound T1969(normal) max_bytes_used: 17270158 Actual T1969(normal) max_bytes_used: 18071064 Deviation T1969(normal) max_bytes_used: 20.3 % *** unexpected stat test failure for T1969(normal) }}} One of these patches is the culprit, but I can't tell from the build logs because the build was broken between these two points: {{{ commit 6a4dc891fa7a8024d8f9f03b98ad675ff5fcbd91 Author: Ömer Sinan Ağacan Bump Haddock submodule commit 8d4760fb7b20682cb5e470b24801301cfbbdce3b Author: Simon Peyton Jones Comments re ApThunks + small refactor in mkRhsClosure commit 9c54185b26922d88e516942aad946f05f707d7ce Author: Simon Peyton Jones Comments + tiny refactor of isNullarySrcDataCon commit a09c0e3e68c96882a1fb392c9dbeea84056bf32f Author: Simon Peyton Jones Comments only commit 714bebff44076061d0a719c4eda2cfd213b7ac3d Author: Ömer Sinan Ağacan Implement unboxed sum primitive type }}} The patch immediately preceding this sequence does not have the failure: https://phabricator.haskell.org/rGHC83e4f49577665278fe08fbaafe2239553f3c448e (follow the link to the build) and the final patch in this sequence *does* have the failure: https://phabricator.haskell.org/rGHC6a4dc891fa7a8024d8f9f03b98ad675ff5fcbd91 (along with an improvement in T9675) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 26 14:56:43 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 26 Jul 2016 14:56:43 -0000 Subject: [GHC] #12438: DeriveDataTypeable - deriving instance Data (Mu (Const ())) Message-ID: <048.d4deec05c6f31ed2d01747b4defade16@haskell.org> #12438: DeriveDataTypeable - deriving instance Data (Mu (Const ())) -------------------------------------+------------------------------------- Reporter: lspitzner | Owner: 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 DeriveDataTypeable, StandaloneDeriving, PolyKinds #-} import qualified Data.Data data Mu f = Mu (f (Mu f)) deriving instance Data.Data.Data (Mu (Const ())) }}} produces {{{ • No instance for (Data (Const () (Mu (Const ())))) arising from a use of ‘k’ • In the expression: (z Mu `k` a1) In an equation for ‘gfoldl’: gfoldl k z (Mu a1) = (z Mu `k` a1) When typechecking the code for ‘gfoldl’ in a derived instance for ‘Data (Mu (Const ()))’: To see the code I am typechecking, use -ddump-deriv In the instance declaration for ‘Data (Mu (Const ()))’ }}} while other type constructors work, e.g. {{{#!hs deriving instance Data.Data.Data (Mu []) deriving instance Data.Data.Data (Mu ((,) ())) }}} i am not sure if #10835 is related. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 26 14:59:23 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 26 Jul 2016 14:59:23 -0000 Subject: [GHC] #12438: DeriveDataTypeable - deriving instance Data (Mu (Const ())) In-Reply-To: <048.d4deec05c6f31ed2d01747b4defade16@haskell.org> References: <048.d4deec05c6f31ed2d01747b4defade16@haskell.org> Message-ID: <063.c4ec0ded190e11d004912f3378198586@haskell.org> #12438: DeriveDataTypeable - deriving instance Data (Mu (Const ())) -------------------------------------+------------------------------------- Reporter: lspitzner | Owner: 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 lspitzner: @@ -2,1 +2,1 @@ - {-# LANGUAGE DeriveDataTypeable, StandaloneDeriving, PolyKinds #-} + {-# LANGUAGE DeriveDataTypeable, StandaloneDeriving #-} New description: {{{#!hs {-# LANGUAGE DeriveDataTypeable, StandaloneDeriving #-} import qualified Data.Data data Mu f = Mu (f (Mu f)) deriving instance Data.Data.Data (Mu (Const ())) }}} produces {{{ • No instance for (Data (Const () (Mu (Const ())))) arising from a use of ‘k’ • In the expression: (z Mu `k` a1) In an equation for ‘gfoldl’: gfoldl k z (Mu a1) = (z Mu `k` a1) When typechecking the code for ‘gfoldl’ in a derived instance for ‘Data (Mu (Const ()))’: To see the code I am typechecking, use -ddump-deriv In the instance declaration for ‘Data (Mu (Const ()))’ }}} while other type constructors work, e.g. {{{#!hs deriving instance Data.Data.Data (Mu []) deriving instance Data.Data.Data (Mu ((,) ())) }}} i am not sure if #10835 is related. -- -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 26 15:03:34 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 26 Jul 2016 15:03:34 -0000 Subject: [GHC] #12439: DeriveDataTypeable - deriving Data for several type constructor applications Message-ID: <048.ddc69e4fd5a90cb2d727e0e34d26bd92@haskell.org> #12439: DeriveDataTypeable - deriving Data for several type constructor applications -------------------------------------+------------------------------------- Reporter: lspitzner | Owner: 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 DeriveDataTypeable, StandaloneDeriving #-} import qualified Data.Data data Mu f = Mu (f (Mu f)) deriving instance Data.Data.Data (Mu []) deriving instance Data.Data.Data (Mu IO) }}} produces {{{ Multiple declarations of ‘$t3Ecq4GuAmh1HtkHHwEpyjp’ [..] Multiple declarations of ‘$c3Ecq4GuAmh1HtkHHwEpyjp’ [..] Duplicate type signatures for ‘$t3Ecq4GuAmh1HtkHHwEpyjp’ [..] Duplicate type signatures for ‘$c3Ecq4GuAmh1HtkHHwEpyjp’ [..] }}} As a workaround one can define instances in separate modules. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 26 15:04:14 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 26 Jul 2016 15:04:14 -0000 Subject: [GHC] #12419: Scheduling bug with forkOS + MVar In-Reply-To: <050.3157bd68c480bed634d3591e7003b69b@haskell.org> References: <050.3157bd68c480bed634d3591e7003b69b@haskell.org> Message-ID: <065.76fa8231f854bf70f718ec900ab32977@haskell.org> #12419: Scheduling bug with forkOS + MVar -------------------------------------+------------------------------------- Reporter: luisgabriel | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Runtime System | Version: 8.0.1 Resolution: | Keywords: forkOS; | scheduler 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 simonmar): The .zip file doesn't download for me (I get an error from dropbox), could you try putting it up somewhere else? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 26 15:07:56 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 26 Jul 2016 15:07:56 -0000 Subject: [GHC] #12419: Scheduling bug with forkOS + MVar In-Reply-To: <050.3157bd68c480bed634d3591e7003b69b@haskell.org> References: <050.3157bd68c480bed634d3591e7003b69b@haskell.org> Message-ID: <065.40863cfeb26292dfc523910313b1f756@haskell.org> #12419: Scheduling bug with forkOS + MVar -------------------------------------+------------------------------------- Reporter: luisgabriel | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Runtime System | Version: 8.0.1 Resolution: | Keywords: forkOS; | scheduler 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 luisgabriel): Replying to [comment:1 simonmar]: > The .zip file doesn't download for me (I get an error from dropbox), could you try putting it up somewhere else? Sure. Try this link: http://cin.ufpe.br/~lgnfl/files/fasta-bug.zip -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 26 16:30:13 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 26 Jul 2016 16:30:13 -0000 Subject: [GHC] #12424: RTS stats show wrong productivity. In-Reply-To: <048.dd6f8ee273b20f973d503ab841f85657@haskell.org> References: <048.dd6f8ee273b20f973d503ab841f85657@haskell.org> Message-ID: <063.871b3d66b93ff55fc921faf447e90520@haskell.org> #12424: RTS stats show wrong productivity. -----------------------------------+-------------------------------------- Reporter: vagarenko | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Runtime System | Version: 8.0.1 Resolution: | Keywords: Operating System: Windows | Architecture: x86_64 (amd64) Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -----------------------------------+-------------------------------------- Comment (by Simon Marlow ): In [changeset:"1783011726a355ac7647246699d43bc7d8b6d9f1/ghc" 17830117/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="1783011726a355ac7647246699d43bc7d8b6d9f1" Fix productivity calculation (#12424) }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 26 16:32:20 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 26 Jul 2016 16:32:20 -0000 Subject: [GHC] #12424: RTS stats show wrong productivity. In-Reply-To: <048.dd6f8ee273b20f973d503ab841f85657@haskell.org> References: <048.dd6f8ee273b20f973d503ab841f85657@haskell.org> Message-ID: <063.260608a0e33110801a50e33a8f1596e0@haskell.org> #12424: RTS stats show wrong productivity. -----------------------------------+-------------------------------------- Reporter: vagarenko | Owner: Type: bug | Status: merge Priority: normal | Milestone: 8.0.2 Component: Runtime System | Version: 8.0.1 Resolution: | Keywords: Operating System: Windows | Architecture: x86_64 (amd64) Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -----------------------------------+-------------------------------------- Changes (by simonmar): * status: new => merge * milestone: => 8.0.2 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 26 18:32:00 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 26 Jul 2016 18:32:00 -0000 Subject: [GHC] #12432: TypeInType: open type family application as type family return kind fails to compile In-Reply-To: <046.81766c43f1232218e828bba3b4f71960@haskell.org> References: <046.81766c43f1232218e828bba3b4f71960@haskell.org> Message-ID: <061.4e565bfa2f6be7c74530f2c7bc74f0d4@haskell.org> #12432: TypeInType: open type family application as type family return kind fails to compile -------------------------------------+------------------------------------- Reporter: j6carey | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.1 checker) | Resolution: duplicate | Keywords: Operating System: Linux | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by j6carey): * Attachment "Test4.hs" added. An application of an associated type family with the kind problem mentioned. Also includes a workaround. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 26 18:41:42 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 26 Jul 2016 18:41:42 -0000 Subject: [GHC] #12440: Strictness of span and break does not match documentation Message-ID: <047.26448c026cd14e209b96449f1c5ed639@haskell.org> #12440: Strictness of span and break does not match documentation -------------------------------------+------------------------------------- Reporter: rwbarton | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: | Version: 8.0.1 libraries/base | 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 [http://hackage.haskell.org/package/base-4.9.0.0/docs/Prelude.html#v:span documentation] of `span` says `span p xs` is equivalent to `(takeWhile p xs, dropWhile p xs)` However, that's not literally true since `span p xs` is _|_ if either `xs` is _|_ or `xs = x :_` and `p x` is _|_. This same error is also present in the Haskell 98 report, which states the same property of `span` but gives a definition equivalent to the one used by GHC. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 26 18:45:13 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 26 Jul 2016 18:45:13 -0000 Subject: [GHC] #12432: TypeInType: open type family application as type family return kind fails to compile In-Reply-To: <046.81766c43f1232218e828bba3b4f71960@haskell.org> References: <046.81766c43f1232218e828bba3b4f71960@haskell.org> Message-ID: <061.4b54aebe8083e627e91c590921261851@haskell.org> #12432: TypeInType: open type family application as type family return kind fails to compile -------------------------------------+------------------------------------- Reporter: j6carey | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.1 checker) | Resolution: duplicate | Keywords: Operating System: Linux | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by j6carey): Because of a workaround (as mentioned below), I don't have a compelling use case at present. The application I had in mind is illustrated by the recently-added attachment, "Test4.hs". The idea is that you have types that express formulas for values, and these can be evaluated in the context of various run-time parameters, though for brevity I have omitted the type expressions whose values actually depend on run-time parameters. Because some of these expressions will determine the sizes of certain objects in memory, I would like optimize length checks by computing static bounds on the range of sizes that a given type expression might specify. In particular, the expression might be a constant of kind "Nat". The associated type family exhibiting the problem is the one that computes the static bounds for the values associated with type expressions. The straightforward instance definition for constants of kind 'Nat' triggers the problem. On the other hand, I have managed to work around the issue by using a helper type family; please see the comment about 'EvalSingleton'. (Minor detail: this excerpt is missing certain features such as checking that the 'Nat' is in bounds, and recovering in some fashion, such as forcing it into the bounds or triggering a compilation error. This is still just a toy example, though hopefully more illustrative of the intended use case.) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 26 22:21:50 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 26 Jul 2016 22:21:50 -0000 Subject: [GHC] #12441: Conflicting definitions error does not print explicit quantifiers when necessary Message-ID: <045.c17febc228a9db8632bc6adb53d95df5@haskell.org> #12441: Conflicting definitions error does not print explicit quantifiers when necessary -------------------------------------+------------------------------------- Reporter: ezyang | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 (Type checker) | 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: -------------------------------------+------------------------------------- {{{ -- Y.hs-boot {-# LANGUAGE ScopedTypeVariables #-} module Y where f :: forall a b. (a, b) -- YY.hs module YY where import {-# SOURCE #-} Y -- Y.hs {-# LANGUAGE ScopedTypeVariables #-} module Y where import YY f :: forall b a. (a, b) f = undefined }}} I get the following unhelpful error: {{{ ezyang at sabre:~$ ghc-8.0 --make Y.hs -fforce-recomp [1 of 3] Compiling Y[boot] ( Y.hs-boot, Y.o-boot ) [2 of 3] Compiling YY ( YY.hs, YY.o ) [3 of 3] Compiling Y ( Y.hs, Y.o ) Y.hs-boot:3:1: error: Identifier ‘f’ has conflicting definitions in the module and its hs-boot file Main module: f :: (a, b) Boot file: f :: (a, b) The two types are different }}} Yes this example is purposely shooting itself in the foot, but in the wild I encountered an un-annotated type which inferred a different quantifier ordering than what I expected, and I subsequently spent a while puzzling over the error message. `-fprint-explicit-foralls` is a sufficient workaround. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 27 15:19:36 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 27 Jul 2016 15:19:36 -0000 Subject: [GHC] #12419: Scheduling bug with forkOS + MVar In-Reply-To: <050.3157bd68c480bed634d3591e7003b69b@haskell.org> References: <050.3157bd68c480bed634d3591e7003b69b@haskell.org> Message-ID: <065.62d1b0f27aa3b81357167bc89b4661b2@haskell.org> #12419: Scheduling bug with forkOS + MVar -------------------------------------+------------------------------------- Reporter: luisgabriel | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Runtime System | Version: 8.0.1 Resolution: | Keywords: forkOS; | scheduler Operating System: Linux | Architecture: x86_64 | (amd64) Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2430 Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonmar): * differential: => Phab:D2430 Comment: I found one bug, see Phab:D2430. However, even after the patch the threadscope profiles don't look identical. I don't think there is an actual problem, just that the program itself isn't very parallel - if you zoom in, there's lots of time in each thread where no work is being done. The difference in scheduling is due to the way that `forkOS` has to hand- shake with the new thread to get its `ThreadId`. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 27 17:42:36 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 27 Jul 2016 17:42:36 -0000 Subject: [GHC] #11470: Support changing cross compiler target at runtime In-Reply-To: <045.fac441a3726b1539e9f173129f6fb28c@haskell.org> References: <045.fac441a3726b1539e9f173129f6fb28c@haskell.org> Message-ID: <060.20520f16df57bf450e58f3a5be462063@haskell.org> #11470: Support changing cross compiler target at runtime -------------------------------------+------------------------------------- Reporter: ezyang | Owner: Type: feature request | Status: new Priority: normal | Milestone: 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: #11378 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by aosivitz): * cc: aosivitz (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 27 19:17:33 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 27 Jul 2016 19:17:33 -0000 Subject: [GHC] #12177: Relevant bindings includes shadowed bindings In-Reply-To: <045.0e76a562090c9d87371f445f74b8515d@haskell.org> References: <045.0e76a562090c9d87371f445f74b8515d@haskell.org> Message-ID: <060.6ef6e0e2f09191f261bcd2bbac1c171c@haskell.org> #12177: Relevant bindings includes shadowed bindings -------------------------------------+------------------------------------- Reporter: ezyang | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.1 checker) | 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 anniecherkaev): I think I've got it working! I'll work through the contributing a patch guide and try submitting a patch later today or tomorrow! -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 27 20:25:07 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 27 Jul 2016 20:25:07 -0000 Subject: [GHC] #12177: Relevant bindings includes shadowed bindings In-Reply-To: <045.0e76a562090c9d87371f445f74b8515d@haskell.org> References: <045.0e76a562090c9d87371f445f74b8515d@haskell.org> Message-ID: <060.77f4196915c4ed9a51c3905d751797dc@haskell.org> #12177: Relevant bindings includes shadowed bindings -------------------------------------+------------------------------------- Reporter: ezyang | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.1 checker) | 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 ezyang): anniecherkaev: That's awesome! I'll be happy to review your patch, keep us posted. Let me know if you have any questions. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 27 20:36:48 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 27 Jul 2016 20:36:48 -0000 Subject: [GHC] #12442: Pure unifier usually doesn't need to unify kinds Message-ID: <047.e9e2d8cc959848de0b431837d76e1a6f@haskell.org> #12442: Pure unifier usually doesn't need to unify kinds -------------------------------------+------------------------------------- Reporter: goldfire | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 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: -------------------------------------+------------------------------------- The pure unifier (in `types/Unify.hs`) is used to match up instances with actual types. Since GHC 8, it matches up the kinds with the types in a separate pass. But this is often wasteful, and sometimes downright wrong. It's wasteful because most invocations of the unifier on a list of types pass in well-kinded arguments to some type constructor. Because the kinds of type constructors are closed, if we process the list left-to-right, we will always unify the kinds of later arguments before we get to them. So we shouldn't take another pass on the kinds. It's wrong because it's conceivable for the kind to include a type family application, and using a type family application as a template in the pure unifier is very silly, indeed. I cam across this while trying to translate Idris's algebraic effects library to Haskell. My reduced test case is attached. Patch on the way. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 27 20:37:04 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 27 Jul 2016 20:37:04 -0000 Subject: [GHC] #12442: Pure unifier usually doesn't need to unify kinds In-Reply-To: <047.e9e2d8cc959848de0b431837d76e1a6f@haskell.org> References: <047.e9e2d8cc959848de0b431837d76e1a6f@haskell.org> Message-ID: <062.bf6dfac71fc0df53c376969eea6fc3a1@haskell.org> #12442: Pure unifier usually doesn't need to unify kinds -------------------------------------+------------------------------------- Reporter: goldfire | Owner: 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: | -------------------------------------+------------------------------------- Changes (by goldfire): * Attachment "Effect.hs" added. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 27 20:46:49 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 27 Jul 2016 20:46:49 -0000 Subject: [GHC] #12443: DEFAULT_TMPDIR is documented, but doesn't exist Message-ID: <047.edde35b3f67cb5f9ea6388079fa88a02@haskell.org> #12443: DEFAULT_TMPDIR is documented, but doesn't exist -------------------------------------+------------------------------------- Reporter: rwbarton | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Documentation | Version: 8.0.1 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: -------------------------------------+------------------------------------- The user's guide claims {{{ Even better idea: Set the :envvar:`DEFAULT_TMPDIR` :command:`make` variable when building GHC, and never worry about :envvar:`TMPDIR` again. (see the build documentation). }}} But only vestiges of this functionality remain in `mk/config.mk.in` and in `nofib`, and it doesn't appear to actually do anything. I suggest removing it from the documentation. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 28 02:23:46 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 28 Jul 2016 02:23:46 -0000 Subject: [GHC] #12442: Pure unifier usually doesn't need to unify kinds In-Reply-To: <047.e9e2d8cc959848de0b431837d76e1a6f@haskell.org> References: <047.e9e2d8cc959848de0b431837d76e1a6f@haskell.org> Message-ID: <062.e62097b3f98487cd42e16b7550923927@haskell.org> #12442: Pure unifier usually doesn't need to unify kinds -------------------------------------+------------------------------------- Reporter: goldfire | Owner: Type: bug | Status: patch 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): Phab:D2433 Wiki Page: | -------------------------------------+------------------------------------- Changes (by goldfire): * status: new => patch * differential: => Phab:D2433 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 28 05:08:52 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 28 Jul 2016 05:08:52 -0000 Subject: [GHC] #12444: Regression: panic! on inaccessible code with constraint Message-ID: <045.55648cb12988a97c56d5e3236e93c6be@haskell.org> #12444: Regression: panic! on inaccessible code with constraint -------------------------------------+------------------------------------- Reporter: zilinc | Owner: 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 Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- Running the following program with ghci-8.0.1: {{{#!hs {-# LANGUAGE DataKinds #-} {-# LANGUAGE GADTs #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE TypeOperators #-} module Prove where data Nat = Zero | Succ Nat data SNat (n :: Nat) where SZero :: SNat Zero SSucc :: SNat n -> SNat (Succ n) type family (:+:) (a :: Nat) (b :: Nat) :: Nat where m :+: Zero = m m :+: (Succ n) = Succ (m :+: n) sadd :: ((Succ n1 :+: n) ~ Succ (n1 :+: n), (Succ n1) ~ m) => SNat m -> SNat n -> SNat (m :+: n) sadd SZero n = n }}} -ddump-tc-trace shows: {{{ ... dischargeFmv s_a9qV[fuv:4] = t_a9qW[tau:5] (1 kicked out) doTopReactFunEq (occurs) old_ev: [D] _ :: ((n1_a9qu[sk] :+: 'Succ s_a9qV[fuv:4]) :: Nat) GHC.Prim.~# (s_a9qV[fuv:4] :: Nat)ghc: panic! (the 'impossible' happened) (GHC version 8.0.1 for x86_64-unknown-linux): ctEvCoercion [D] _ :: (t_a9qW[tau:5] :: Nat) ~# ('Succ (n1_a9qu[sk] :+: s_a9qV[fuv:4]) :: Nat) Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug }}} It is rightly rejected by ghci-7.10.2: {{{ Prove.hs:42:6: Couldn't match type ‘'Succ n1’ with ‘'Zero’ Inaccessible code in a pattern with constructor SZero :: SNat 'Zero, in an equation for ‘sadd’ In the pattern: SZero In an equation for ‘sadd’: sadd SZero n = n Failed, modules loaded: none. }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 28 11:01:26 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 28 Jul 2016 11:01:26 -0000 Subject: [GHC] #12445: showSDocUnsafe generate GHC panic Message-ID: <042.cc37bc6363a5b60ad0575da7639d5766@haskell.org> #12445: showSDocUnsafe generate GHC panic -------------------------------------+------------------------------------- Reporter: Bet | Owner: Type: bug | Status: new Priority: normal | Milestone: ⊥ Component: GHC API | Version: 7.10.3 Keywords: GHC panic | Operating System: Unknown/Multiple Architecture: | Type of failure: Runtime crash Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- Try in ghci: {{{#!hs :set -package ghc :m Outputable let x = text "SomeDoc" showSDocUnsafe x }}} The code abobe generate: "ghc.exe: panic! (the 'impossible' happened) (GHC version 7.10.3 for x86_64-unknown-mingw32): v_unsafeGlobalDynFlags: not initialised 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 Thu Jul 28 11:50:01 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 28 Jul 2016 11:50:01 -0000 Subject: [GHC] #12445: showSDocUnsafe generate GHC panic In-Reply-To: <042.cc37bc6363a5b60ad0575da7639d5766@haskell.org> References: <042.cc37bc6363a5b60ad0575da7639d5766@haskell.org> Message-ID: <057.c0aba9db8a638d282a873b1f1b6ce206@haskell.org> #12445: showSDocUnsafe generate GHC panic -------------------------------------+------------------------------------- Reporter: Bet | Owner: Type: bug | Status: closed Priority: normal | Milestone: ⊥ Component: GHC API | Version: 7.10.3 Resolution: invalid | Keywords: GHC panic Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Runtime crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by mpickering): * status: new => closed * resolution: => invalid Comment: The function is called `showSDocUnsafe` precisely for this reason, it is unsafe..! You should use `showSDoc` if you want more safety guarantees. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 28 12:21:41 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 28 Jul 2016 12:21:41 -0000 Subject: [GHC] #12083: ghc-8.0.1-rc4: tyConRoles sees a TcTyCon In-Reply-To: <048.a4a2a5816a0aa4dfbaf2640f489bd6c3@haskell.org> References: <048.a4a2a5816a0aa4dfbaf2640f489bd6c3@haskell.org> Message-ID: <063.3ecf7ceea74ed68bb83ab17cfe2b346d@haskell.org> #12083: ghc-8.0.1-rc4: tyConRoles sees a TcTyCon -------------------------------------+------------------------------------- Reporter: _deepfire | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.1-rc4 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Yes. Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by mniip): I just hit what I think is an instance of this bug, but in a completely different setup. So here's another testcase I guess: {{{ {-# LANGUAGE GADTs #-} module Bug where class Class a where test :: a -> (Eq a => r) -> r data P a b where Con :: (Class a, a ~ b) => P a b }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 28 14:44:45 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 28 Jul 2016 14:44:45 -0000 Subject: [GHC] #12121: FlexibleContexts is under specified In-Reply-To: <045.d85403886ed965b098b403fa737d3a40@haskell.org> References: <045.d85403886ed965b098b403fa737d3a40@haskell.org> Message-ID: <060.432606c6a7f695b21cfadf424c801fda@haskell.org> #12121: FlexibleContexts is under specified -------------------------------------+------------------------------------- Reporter: thomie | Owner: thomie 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: #12120 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by mpickering): * cc: mpickering (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 28 15:52:06 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 28 Jul 2016 15:52:06 -0000 Subject: [GHC] #12432: TypeInType: open type family application as type family return kind fails to compile In-Reply-To: <046.81766c43f1232218e828bba3b4f71960@haskell.org> References: <046.81766c43f1232218e828bba3b4f71960@haskell.org> Message-ID: <061.46bd0958bb35bec30b8900f6a325e0d7@haskell.org> #12432: TypeInType: open type family application as type family return kind fails to compile -------------------------------------+------------------------------------- Reporter: j6carey | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.1 checker) | Resolution: duplicate | Keywords: Operating System: Linux | 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 example also has another problem: forgetting about lifted equality and such, an associated type cannot assume any context of an instance. This is because an associated type instance is effectively floated out of the class and behaves identically to a standalone type instance. Associated types just give you some nice syntax -- and that's it.... but maybe we need to revisit all of this, and perhaps allow type instances to specify a context. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 28 16:53:56 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 28 Jul 2016 16:53:56 -0000 Subject: [GHC] #12177: Relevant bindings includes shadowed bindings In-Reply-To: <045.0e76a562090c9d87371f445f74b8515d@haskell.org> References: <045.0e76a562090c9d87371f445f74b8515d@haskell.org> Message-ID: <060.c8a55e426cd196b7177591d30fa31e34@haskell.org> #12177: Relevant bindings includes shadowed bindings -------------------------------------+------------------------------------- Reporter: ezyang | Owner: Type: bug | Status: patch Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.1 checker) | 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:D2434 Wiki Page: | -------------------------------------+------------------------------------- Changes (by anniecherkaev): * status: new => patch * differential: => Phab:D2434 Comment: Great, thanks! I just got a patch up on Phabricator. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 28 18:06:34 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 28 Jul 2016 18:06:34 -0000 Subject: [GHC] #12446: Doesn't suggest TypeApplications when `~` used prefix Message-ID: <051.fbdff3a41aaa6fb6f877bb677e6f69a8@haskell.org> #12446: Doesn't suggest TypeApplications when `~` used prefix -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: 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: -------------------------------------+------------------------------------- {{{ $ ghci -ignore-dot-ghci GHCi, version 8.0.1: http://www.haskell.org/ghc/ :? for help Prelude> :t undefined @(_ ~ _) :1:1: error: Pattern syntax in expression context: undefined@(_ (~(_))) Did you mean to enable TypeApplications? }}} It is suggested with non-`~` type operators {{{ Prelude> :t undefined @((+) _ _) :1:1: error: Pattern syntax in expression context: undefined@((+) (_) (_)) Did you mean to enable TypeApplications? }}} but not with {{{ Prelude> :t undefined @((~) _ _) :1:15: error: parse error on input ‘)’ }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 28 20:17:41 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 28 Jul 2016 20:17:41 -0000 Subject: [GHC] #12447: Pretty-printing of equality `~` without parentheses Message-ID: <051.dba18f323b8c18d3270065a172f0294e@haskell.org> #12447: Pretty-printing of equality `~` without parentheses -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: 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: -------------------------------------+------------------------------------- Based off on [https://github.com/ekmett/constraints/blob/master/src/Data/Constraint/Deferrable.hs Data.Constraint.Deferrable] {{{#!hs {-# Language RankNTypes, ConstraintKinds #-} import Data.Typeable class Deferrable p where deferEither :: proxy p -> (p => r) -> Either String r instance (Typeable a, Typeable b) => Deferrable (a ~ b) where deferEither = undefined }}} `PolyKinds` aren't enabled so `deferEither @(_ ~ _)` is not enough to select the `Deferrable (a ~ b)` instance, but it is displayed without parentheses {{{ $ ghci -XTypeApplications -ignore-dot-ghci tyiS.hs GHCi, version 8.0.1: http://www.haskell.org/ghc/ :? for help [1 of 1] Compiling Main ( tyiS.hs, interpreted ) Ok, modules loaded: Main. *Main> :t deferEither @(_ ~ _) deferEither @(_ ~ _) :: Deferrable t ~ t1 => proxy t ~ t1 -> (t ~ t1 => r) -> Either String r }}} Instead of a preferable {{{#!hs deferEither @(_ ~ _) :: Deferrable (t ~ t1) => proxy (t ~ t1) -> (t ~ t1 => r) -> Either String r }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 29 00:03:13 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 29 Jul 2016 00:03:13 -0000 Subject: [GHC] #12422: Add decidable equality class In-Reply-To: <045.cc846fa4626d50a4033ca66a47264374@haskell.org> References: <045.cc846fa4626d50a4033ca66a47264374@haskell.org> Message-ID: <060.0cd0e70af5a39effedb09cbbba390489@haskell.org> #12422: Add decidable equality class -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: 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): * cc: RyanGlScott (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 29 01:11:57 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 29 Jul 2016 01:11:57 -0000 Subject: [GHC] #12447: Pretty-printing of equality `~` without parentheses In-Reply-To: <051.dba18f323b8c18d3270065a172f0294e@haskell.org> References: <051.dba18f323b8c18d3270065a172f0294e@haskell.org> Message-ID: <066.ad9e3952ec02f4139a6aede4f1a5d8bc@haskell.org> #12447: Pretty-printing of equality `~` without parentheses -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: 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): Same with {{{#!hs {-# Language KindSignatures, TypeOperators #-} import Data.Kind import Data.Type.Equality class Foo (p :: Constraint) instance Foo (a ~ b) instance Foo (a ~~ b) }}} {{{ $ ghci -ignore-dot-ghci /tmp/tOrO.hs GHCi, version 8.0.1: http://www.haskell.org/ghc/ :? for help [1 of 1] Compiling Main ( /tmp/tOrO.hs, interpreted ) Ok, modules loaded: Main. *Main> :i Foo class Foo (p :: Constraint) -- Defined at /tmp/tOrO.hs:6:1 instance [safe] Foo a ~ b -- Defined at /tmp/tOrO.hs:8:10 }}} {{{ *Main> :set -fprint-equality-relations *Main> :i Foo class Foo (p :: Constraint) -- Defined at /tmp/tOrO.hs:6:1 instance [safe] Foo (a :: *) ~~ (b :: *) -- Defined at /tmp/tOrO.hs:8:10 }}} Should be ` {{{ *Main> :i Foo class Foo (p :: Constraint) -- Defined at /tmp/tOrO.hs:6:1 instance [safe] Foo (a ~ b) -- Defined at /tmp/tOrO.hs:8:10 *Main> :set -fprint-equality-relations *Main> :i Foo class Foo (p :: Constraint) -- Defined at /tmp/tOrO.hs:6:1 instance [safe] Foo ((a :: *) ~~ (b :: *)) -- Defined at /tmp/tOrO.hs:8:10 }}} ---- Is this the same as #12005, two instances are defined: {{{#!hs instance Foo (a ~ b) instance Foo (a ~~ b) }}} but only one displayed in `:info`: is the first subsumed by the latter? There is some funny business going on in the [https://hackage.haskell.org/package/base-4.9.0.0/docs/Data-Type- Equality.html#t:-126--126- definition of ‘~~’] so I don't know if those are separate instances. For example what is the difference between these two instances `↓`? {{{#!hs instance Foo (a ~ b) instance Foo ((a::Type) ~~ (b::Type)) }}} Again, only the latter is displayed: {{{#!hs *Main> :i Foo class Foo (p :: Constraint) -- Defined at /tmp/tOrO.hs:6:1 instance [safe] Foo a ~ b -- Defined at /tmp/tOrO.hs:8:10 *Main> :set -fprint-equality-relations *Main> :i Foo class Foo (p :: Constraint) -- Defined at /tmp/tOrO.hs:6:1 instance [safe] Foo (a :: *) ~~ (b :: *) -- Defined at /tmp/tOrO.hs:8:10 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 29 13:07:34 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 29 Jul 2016 13:07:34 -0000 Subject: [GHC] #11011: Add type-indexed type representations (`TypeRep a`) In-Reply-To: <047.c73f466ae3b4d7fe3bfc6781e66855ef@haskell.org> References: <047.c73f466ae3b4d7fe3bfc6781e66855ef@haskell.org> Message-ID: <062.489dcc15b392e5efa74a0b572d608511@haskell.org> #11011: Add type-indexed type representations (`TypeRep a`) -------------------------------------+------------------------------------- Reporter: bjmprice | Owner: Type: feature request | 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:D2010 Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * cc: RyanGlScott (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 29 15:05:27 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 29 Jul 2016 15:05:27 -0000 Subject: [GHC] #10343: Make Typeable track kind information better In-Reply-To: <045.85e9bb0ccd5b9cbce8f9c98e97306bc2@haskell.org> References: <045.85e9bb0ccd5b9cbce8f9c98e97306bc2@haskell.org> Message-ID: <060.9153c831e7fe3ae4a530d7de7b271a91@haskell.org> #10343: Make Typeable track kind information better -------------------------------------+------------------------------------- Reporter: oerjan | Owner: goldfire Type: feature request | Status: new Priority: normal | Milestone: 8.2.1 Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Typeable Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: typeOf :: | Typeable (a::k) => Proxy a -> | TypeRep Blocked By: | Blocking: Related Tickets: #9858, #11011 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * related: #9858 => #9858, #11011 Comment: For the record, this will be addressed in the solution of #11011 which should be coming in GHC 8.2. See Typeable/BenGamari for details. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 29 22:34:43 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 29 Jul 2016 22:34:43 -0000 Subject: [GHC] #8581: Pattern synonym used in an expression context could have different constraints to pattern used in a pattern context In-Reply-To: <045.ffb8b433d262c0e3b5b415c2eeca2eee@haskell.org> References: <045.ffb8b433d262c0e3b5b415c2eeca2eee@haskell.org> Message-ID: <060.db0a045a973bb90fa653218e38183f4c@haskell.org> #8581: Pattern synonym used in an expression context could have different constraints to pattern used in a pattern context -------------------------------------+------------------------------------- Reporter: cactus | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 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 dfeuer): If we let the constructor have its own signature, can we drop the whole required constraints bit? If so, I think that would make things considerably less confusing. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jul 30 04:41:52 2016 From: ghc-devs at haskell.org (GHC) Date: Sat, 30 Jul 2016 04:41:52 -0000 Subject: [GHC] #11011: Add type-indexed type representations (`TypeRep a`) In-Reply-To: <047.c73f466ae3b4d7fe3bfc6781e66855ef@haskell.org> References: <047.c73f466ae3b4d7fe3bfc6781e66855ef@haskell.org> Message-ID: <062.44f489bed96489d17d596b5e216f433f@haskell.org> #11011: Add type-indexed type representations (`TypeRep a`) -------------------------------------+------------------------------------- Reporter: bjmprice | Owner: Type: feature request | 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:D2010 Wiki Page: | -------------------------------------+------------------------------------- Changes (by oerjan): * cc: oerjan (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jul 30 08:46:52 2016 From: ghc-devs at haskell.org (GHC) Date: Sat, 30 Jul 2016 08:46:52 -0000 Subject: [GHC] #8581: Pattern synonym used in an expression context could have different constraints to pattern used in a pattern context In-Reply-To: <045.ffb8b433d262c0e3b5b415c2eeca2eee@haskell.org> References: <045.ffb8b433d262c0e3b5b415c2eeca2eee@haskell.org> Message-ID: <060.a4b412b2f0eb748ad769438976988733@haskell.org> #8581: Pattern synonym used in an expression context could have different constraints to pattern used in a pattern context -------------------------------------+------------------------------------- Reporter: cactus | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 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 cactus): Replying to [comment:43 dfeuer]: > If we let the constructor have its own signature, can we drop the whole required constraints bit? If so, I think that would make things considerably less confusing. But the required constraints don't come from builders; a unidirectional pattern synonym can have just as much of a required context. The simplest example I can think of is {{{ pattern P x <- (f -> x) }}} Here, any constraint of `f` on its argument's type will be a required constraint in `P`'s type. (Note that a special case of this is matching against overloaded literals, e.g. `pattern Z = 0`, which requires `(Num a, Eq a)`.) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jul 30 19:39:57 2016 From: ghc-devs at haskell.org (GHC) Date: Sat, 30 Jul 2016 19:39:57 -0000 Subject: [GHC] #860: CPP fails when a macro is used on a line containing a single quote character In-Reply-To: <054.edee737bcd8885fd96e918b248a30f6e@haskell.org> References: <054.edee737bcd8885fd96e918b248a30f6e@haskell.org> Message-ID: <069.64f6e752fa62351f16d2ea3d342e0a66@haskell.org> #860: CPP fails when a macro is used on a line containing a single quote character -------------------------------------+------------------------------------- Reporter: ketil@… | Owner: Type: feature request | Status: new Priority: lowest | Milestone: ⊥ Component: Compiler | Version: 6.4.2 Resolution: | Keywords: cpp quote | prime 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 Sat Jul 30 19:40:14 2016 From: ghc-devs at haskell.org (GHC) Date: Sat, 30 Jul 2016 19:40:14 -0000 Subject: [GHC] #860: CPP fails when a macro is used on a line containing a single quote character In-Reply-To: <054.edee737bcd8885fd96e918b248a30f6e@haskell.org> References: <054.edee737bcd8885fd96e918b248a30f6e@haskell.org> Message-ID: <069.46605b6caff0efdb7b946adae8e8391e@haskell.org> #860: CPP fails when a macro is used on a line containing a single quote character -------------------------------------+------------------------------------- Reporter: ketil@… | Owner: Type: feature request | Status: new Priority: lowest | Milestone: ⊥ Component: Compiler | Version: 6.4.2 Resolution: | Keywords: cpp quote | prime 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 asr): * cc: asr (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Jul 31 03:52:03 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 31 Jul 2016 03:52:03 -0000 Subject: [GHC] #12448: Allow partial application of bidirectional pattern synonyms Message-ID: <051.59eb353dccca81d445cc47281fa0f4a1@haskell.org> #12448: Allow partial application of bidirectional pattern synonyms -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 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: -------------------------------------+------------------------------------- {{{#!hs type Product3 = (,,) }}} Allow {{{#!hs pattern Product3 :: a -> b -> c -> Product3 a b c pattern Product3 = (,,) }}} to mean {{{#!hs pattern Product3 :: a -> b -> c -> Product3 a b c pattern Product3 x y z = (x, y, z) }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Jul 31 03:52:48 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 31 Jul 2016 03:52:48 -0000 Subject: [GHC] #12448: Allow partial application of bidirectional pattern synonyms In-Reply-To: <051.59eb353dccca81d445cc47281fa0f4a1@haskell.org> References: <051.59eb353dccca81d445cc47281fa0f4a1@haskell.org> Message-ID: <066.01179cc186c758f044e1da91f60a1699@haskell.org> #12448: Allow partial application of bidirectional pattern synonyms -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 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 Iceland_jack): {{{#!hs pattern None = Nothing pattern Some = Just }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Jul 31 05:58:31 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 31 Jul 2016 05:58:31 -0000 Subject: [GHC] #860: CPP fails when a macro is used on a line containing a single quote character In-Reply-To: <054.edee737bcd8885fd96e918b248a30f6e@haskell.org> References: <054.edee737bcd8885fd96e918b248a30f6e@haskell.org> Message-ID: <069.7a57dd87dbf3695dff264378085eb9cf@haskell.org> #860: CPP fails when a macro is used on a line containing a single quote character -------------------------------------+------------------------------------- Reporter: ketil@… | Owner: Type: feature request | Status: new Priority: lowest | Milestone: ⊥ Component: Compiler | Version: 6.4.2 Resolution: | Keywords: cpp quote | prime 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 andreas.abel): > There are other gotchas with CPP (e.g. the backslash-at-the-end-of-the- line thing). See, for instance, ticket:12391 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Jul 31 06:21:13 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 31 Jul 2016 06:21:13 -0000 Subject: [GHC] #12391: LANGUAGE CPP messes up parsing when backslash like \\ is at end of line (eol) In-Reply-To: <051.90ff32b6d904c34082d69eb15f9b624a@haskell.org> References: <051.90ff32b6d904c34082d69eb15f9b624a@haskell.org> Message-ID: <066.fa8f6903f132134ffaf75a30513dca3f@haskell.org> #12391: LANGUAGE CPP messes up parsing when backslash like \\ is at end of line (eol) -------------------------------------+------------------------------------- Reporter: andreas.abel | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 (Parser) | Resolution: | Keywords: CPP 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 andreas.abel): This makes for a nice exploit: {{{#!hs -- {-# LANGUAGE CPP #-} {-# LANGUAGE TemplateHaskell #-} -- for quickCheckAll import Test.QuickCheck.All infixl 6 % infixl 6 %\ -- Was this the correct fixity? (%) :: Int -> Int -> Int x % y = x - y (%\) :: Int -> Int -> Int x %\ y = (x + 1) - y prop_by_def x y = (x + 1) % y == x %\ y return [] -- TH hack main = $quickCheckAll }}} Uncomment the CPP pragma and quickCheck again! -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Jul 31 10:10:51 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 31 Jul 2016 10:10:51 -0000 Subject: [GHC] #11669: Incorrectly suggests RankNTypes for ill-formed type "forall a. Eq a. Int" In-Reply-To: <051.ef9fc6a373cf8eba53b7bf79d29ca288@haskell.org> References: <051.ef9fc6a373cf8eba53b7bf79d29ca288@haskell.org> Message-ID: <066.247156f76f5244e39a551907c330169e@haskell.org> #11669: Incorrectly suggests RankNTypes for ill-formed type "forall a. Eq a. Int" -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.1 (Parser) | 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: #3155 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by jstolarek): Thomie, I am a bit puzzled by your comment. I think that the signature `foo :: forall a. Eq a. Int` is incorrect (even with `ExplicitForAll` or `RankNTypes`) and should be simply rejected with a parse error. Or am I missing something? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Jul 31 10:40:42 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 31 Jul 2016 10:40:42 -0000 Subject: [GHC] #5218: Add unpackCStringLen# to create Strings from string literals In-Reply-To: <044.69091f2248f564745af8f69c26fefc28@haskell.org> References: <044.69091f2248f564745af8f69c26fefc28@haskell.org> Message-ID: <059.45189d9945e3b714678c3e4620684f03@haskell.org> #5218: Add unpackCStringLen# to create Strings from string literals -------------------------------------+------------------------------------- Reporter: tibbe | Owner: thoughtpolice Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.0.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: #5877 #10064 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by jscholl): I tried implementing a {{{String#}}} type which would carry the length as an {{{Int#}}} at its beginning and two functions to extract the length and address of the string literal. However, it quickly got a little bit out of hand: - {{{unpackCString#}}} etc. had to be adopted, breaking backwards compatibility. To avoid this, I tried to create wrapper functions {{{unpackCStringLit#}}}, which would extract the address and call the original {{{unpackCString#}}} function. - I could not solve the question how to adopt the rewrite rules dealing with strings without duplicating them for the {{{Addr#}}} and {{{String#}}} versions. I could also not figure out when {{{unpackCStringLit#}}} should inline to avoid the overhead of the new address computation. - It took a while to find all (most?) of the places (library, some hardcoded types in {{{Id}}}s, a place in the type checker, generating record selector errors) where types where wired in, especially for exceptions like {{{absentError}}} and {{{recSelError}}}. - Implementing a new {{{String#}}} also asked the question whether {{{"foo"##}}} should be the corresponding literal for it. However, adding it from the parser to the backend seemed quite complex, so I tried a different approach. Instead of creating a new type {{{String#}}}, I rewrote {{{unpackCStringLit#}}} to have the type {{{Addr# -> Int# -> [Char]}}}. It would then just throw its second argument away and inline in some phase. However, it still meant duplicating rewrite rules, which seemed not like an idea solution. My next idea was to push the length information into an ignored argument to a function giving us the address: {{{cStringLitAddr# :: Addr# -> Int# -> Addr#}}}. This could just be passed as an argument to {{{unpackCString#}}}, thus I was quite confident that it would remain backwards compatible and no extra rewrite rules were needed to maintain the current behavior (but extra rules to use the length information, e.g. to construct bytestrings, but this seems like an acceptable cost). However, I did not anticipate the let/app invariant, thus my original design of {{{unpackCString# (cStringLitAddr# "foo"# 3#)}}} caused lint to warn me. After reading up about the invariant, I decided that {{{cStringLitAddr#}}}, applied to two literals, should be okay for speculation, as it did not have side effects nor could fail or anything. However, while now the generated core was accepted, it was useless, as it would not match the rewrite rules written by a user. Their rules would be translated to something like {{{case cStringLitAddr# addr len of { tmp -> unpackCString# tmp } }}}. Thus, I decided to generate matching core and removed my fix to make {{{cStringLitAddr#}}} okay for speculation. In the current version, it is possible to create a bytestring in O(1) with rewrite rules. However, I have broken the general list fusion (or at least the built-in rules {{{match_eq_string}}} and {{{match_append_lit}}}), as the case statement gets in the way between {{{foldr}}} and {{{build}}}, causing them to not be optimized out (but maybe this is generally a missed opportunity, if I have {{{foo (case something of { tmp -> bar tmp }) }}}, maybe it should be possible to rewrite {{{foo (bar x) = baz x}}} anyway, leading to {{{case something of { tmp -> baz tmp } }}}, iff {{{something}}} is safe to evaluate with regards to time, space and exceptions (this is okay-for- speculation, right?)). So right now I am stuck. Maybe it is okay to break backwards compatibility and just change the types of {{{unpackCString#}}} etc. to include an additional (ignored) {{{Int#}}} argument, pushing some #ifs to everyone using {{{unpackCString#}}} (I think this is basically text, bytestring and ghc itself) for the next few years. However, {{{unpackCString#}}} is called at some additional places, namely when constructing modules for {{{Typeable}}}. Right now the types only carry the {{{Addr#}}} to call it, but would then also need the length information (or there would be the risk that something rewrites it and gets a bogus length, if one just passes {{{0#}}} as length information). On the other hand, maybe it would be a good thing to actually pass the length along to {{{unpackCString#}}}, making it mandatory, as this would avoid the need to null-terminate the strings, allowing {{{'\NUL'}}} characters to be encoded with one byte instead of two (which may be of interest for bytestring). On the other hand, I could imagine this breaking stuff if strings are no longer null- terminated in subtle ways... -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Jul 31 11:27:24 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 31 Jul 2016 11:27:24 -0000 Subject: [GHC] #12391: LANGUAGE CPP messes up parsing when backslash like \\ is at end of line (eol) In-Reply-To: <051.90ff32b6d904c34082d69eb15f9b624a@haskell.org> References: <051.90ff32b6d904c34082d69eb15f9b624a@haskell.org> Message-ID: <066.4f8eabab98af44289c72f66a3dc01c88@haskell.org> #12391: LANGUAGE CPP messes up parsing when backslash like \\ is at end of line (eol) -------------------------------------+------------------------------------- Reporter: andreas.abel | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 (Parser) | Resolution: | Keywords: CPP 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 asr): * cc: asr (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Jul 31 11:28:06 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 31 Jul 2016 11:28:06 -0000 Subject: [GHC] #11669: Incorrectly suggests RankNTypes for ill-formed type "forall a. Eq a. Int" In-Reply-To: <051.ef9fc6a373cf8eba53b7bf79d29ca288@haskell.org> References: <051.ef9fc6a373cf8eba53b7bf79d29ca288@haskell.org> Message-ID: <066.8d595395a3f058c0145615a5105d56be@haskell.org> #11669: Incorrectly suggests RankNTypes for ill-formed type "forall a. Eq a. Int" -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.1 (Parser) | 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: #3155 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by drobnik): * cc: drobnik (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Jul 31 11:31:06 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 31 Jul 2016 11:31:06 -0000 Subject: [GHC] #11669: Incorrectly suggests RankNTypes for ill-formed type "forall a. Eq a. Int" In-Reply-To: <051.ef9fc6a373cf8eba53b7bf79d29ca288@haskell.org> References: <051.ef9fc6a373cf8eba53b7bf79d29ca288@haskell.org> Message-ID: <066.47e7d9588097da11cde9a7cc61407556@haskell.org> #11669: Incorrectly suggests RankNTypes for ill-formed type "forall a. Eq a. Int" -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.1 (Parser) | 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: #3155 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by jstolarek): * cc: jstolarek (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Jul 31 16:40:48 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 31 Jul 2016 16:40:48 -0000 Subject: [GHC] #12449: Broken types in identifiers bound by :print Message-ID: <044.542a5d089ce4efa7862430871616a137@haskell.org> #12449: Broken types in identifiers bound by :print -------------------------------------+------------------------------------- Reporter: mniip | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: GHCi crash Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- {{{#!hs GHCi, version 8.0.1: http://www.haskell.org/ghc/ :? for help Prelude> :print show show = (_t1::Show a => a -> String) Prelude> :t _t1 :1:1: error: No instance for (Show a) arising from a use of ‘it’ }}} Furthermore: {{{#!hs Prelude> _t1 "foo" :3:5: error:ghc: panic! (the 'impossible' happened) (GHC version 8.0.1 for x86_64-unknown-linux): No skolem info: a_a1hz Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug Prelude> }}} Enabling `-fprint-explicit-foralls`, I think, reveals the issue: {{{#!hs Prelude> :set -fprint-explicit-foralls Prelude> :print id id = (_t2::a1 -> a1) Prelude> :t id id :: forall {a}. a -> a Prelude> :t _t2 _t2 :: a1 -> a1 }}} Similar behavior albeit with a different panic message happens on 7.8.4 and 7.10.3 as verified by bennofs over IRC: {{{ GHCi, version 7.10.3: http://www.haskell.org/ghc/ :? for help Prelude> :print print print = (_t1::Show a => a -> IO ()) Prelude> _t1 ghc: panic! (the 'impossible' happened) (GHC version 7.10.3 for x86_64-unknown-linux): tcTyVarDetails a_apc Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug }}} 7.6.3 doesn't exhibit this issue: {{{ GHCi, version 7.6.3: http://www.haskell.org/ghc/ :? for help Prelude> :print id id = (_t1::forall a. a -> a) }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Jul 31 18:28:48 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 31 Jul 2016 18:28:48 -0000 Subject: [GHC] #12150: Compile time performance degradation on code that uses undefined/error with CallStacks In-Reply-To: <045.a0bd3502ce7a1f35f82939f7b0bb87d6@haskell.org> References: <045.a0bd3502ce7a1f35f82939f7b0bb87d6@haskell.org> Message-ID: <060.02401761b95e7fffe68986ed72661948@haskell.org> #12150: Compile time performance degradation on code that uses undefined/error with CallStacks -------------------------------------+------------------------------------- Reporter: thomie | Owner: Type: bug | Status: new Priority: high | Milestone: 8.0.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: #10844 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by gridaphobe): So, although my no-inline patch is now producing better results for the original CallStack-inlining issue, it doesn't seem to be doing much for this issue. Upon closer inspection of the Core I noticed something quite interesting. When we remove the CallStacks from `undefined`, GHC manages to optimize away the entire set of guards! In stark contrast, leaving the CallStacks gives us the following Core {{{ -- RHS size: {terms: 4, types: 7, coercions: 0} Test.$fFunctorResult_$cfmap [InlPrag=INLINE (sat-args=0)] :: forall a_aFQ b_aFR. (a_aFQ -> b_aFR) -> Result a_aFQ -> Result b_aFR [GblId, Str=b, Unf=Unf{Src=InlineStable, TopLvl=True, Value=False, ConLike=False, WorkFree=False, Expandable=False, Guidance=ALWAYS_IF(arity=0,unsat_ok=False,boring_ok=False) Tmpl= \ (@ a_aFS) (@ b_aFT) -> let { $dIP_s1QH :: GHC.Stack.Types.CallStack [LclId] $dIP_s1QH = GHC.Stack.Types.pushCallStack (Test.$fFunctorResult10, Test.$fFunctorResult8) GHC.Stack.Types.emptyCallStack } in let { bool1_aqS :: forall a1_a1Dw. a1_a1Dw [LclId] bool1_aqS = \ (@ a1_a1Dw) -> undefined @ 'GHC.Types.PtrRepLifted @ a1_a1Dw ($dIP_s1QH `cast` (Sym (GHC.Classes.N:IP[0] <"callStack">_N _N) :: (GHC.Stack.Types.CallStack :: *) ~R# ((?callStack::GHC.Stack.Types.CallStack) :: Constraint))) } in case bool1_aqS @ Bool of { False -> case bool1_aqS @ Bool of { False -> case bool1_aqS @ Bool of { False -> case bool1_aqS @ Bool of { False -> case bool1_aqS @ Bool of { False -> case bool1_aqS @ Bool of { False -> case bool1_aqS @ Bool of { False -> case bool1_aqS @ Bool of { ...] Test.$fFunctorResult_$cfmap = \ (@ a_aFS) (@ b_aFT) -> case bool1_aqS of wild_00 { } }}} So GHC is optimizing the actual definition, but not the unfolding, whereas with the old `undefined` it also optimized the unfolding. I also noticed that I can reproduce both behaviors with a simple wrapper around `undefined`, by choosing whether the wrapper should take a CallStack. {{{ -- myUndef :: HasCallStack => a -- myUndef :: a myUndef = undefined }}} The HasCallStack variant is slow, but the CallStack-free variant behaves just like the old undefined. I suppose this is to be expected, but it seems to suggest that the issue is connected to the fact that a use of `undefined` is now really an application `undefined $call_stack` rather than a simple variable. Indeed, if I make one final tweak to the program and use the **old `error`** instead of `undefined`, I get a similar behavior to the **new** `undefined`. {{{ N clauses : time (s) 10 : 0.44 20 : 0.48 40 : 0.54 80 : 0.76 160 : 1.13 320 : 1.93 640 : 3.52 1280 : 6.97 }}} I'm not really sure where to go from here. It seems like the solution would be to convince GHC to rewrite the unfolding for the new undefined (or error for that matter), but rewriting the unfolding is not something we're supposed to do, right? Which makes me wonder, why was GHC rewriting the unfolding for the old undefined in the first place? -- Ticket URL: GHC The Glasgow Haskell Compiler